[skip ci] [skip sc] generic interfaces for HDF5 operations

most existing HDF5 functions are only designed for writing output files
and more general functionality is needed for storing the restart data
This commit is contained in:
Martin Diehl 2018-10-05 08:56:06 +02:00
parent a6ebdfc1ff
commit a560fff2ac
2 changed files with 72 additions and 44 deletions

View File

@ -126,7 +126,7 @@ subroutine CPFEM_init
use HDF5_utilities, only: & use HDF5_utilities, only: &
HDF5_openFile, & HDF5_openFile, &
HDF5_openGroup2, & HDF5_openGroup2, &
HDF5_readDataSet HDF5_read
use DAMASK_interface, only: & use DAMASK_interface, only: &
getSolverJobName getSolverJobName
@ -135,10 +135,6 @@ subroutine CPFEM_init
character(len=1024) :: rankStr character(len=1024) :: rankStr
integer(HID_T) :: fileReadID, groupPlasticID integer(HID_T) :: fileReadID, groupPlasticID
integer :: hdferr integer :: hdferr
real(pReal), dimension(:,:,:), allocatable :: dummy3
real(pReal), dimension(:,:,:,:,:), allocatable :: dummy5
!dummy = material_phase
!write(6,*) shape(dummy), flush(6)
mainProcess: if (worldrank == 0) then mainProcess: if (worldrank == 0) then
write(6,'(/,a)') ' <<<+- CPFEM init -+>>>' write(6,'(/,a)') ' <<<+- CPFEM init -+>>>'
@ -146,11 +142,10 @@ subroutine CPFEM_init
#include "compilation_info.f90" #include "compilation_info.f90"
flush(6) flush(6)
endif mainProcess endif mainProcess
!restartRead = .true.
! *** restore the last converged values of each essential variable from the binary file ! *** restore the last converged values of each essential variable from the binary file
if (restartRead) then if (restartRead) then
if (iand(debug_level(debug_CPFEM), debug_levelExtensive) /= 0_pInt) then if (iand(debug_level(debug_CPFEM), debug_levelExtensive) /= 0_pInt) then
!write(6,'(a)') '<< CPFEM >> restored state variables of last converged step from binary files'
write(6,'(a)') '<< CPFEM >> restored state variables of last converged step from hdf5 file' write(6,'(a)') '<< CPFEM >> restored state variables of last converged step from hdf5 file'
flush(6) flush(6)
endif endif
@ -158,22 +153,12 @@ subroutine CPFEM_init
write(rankStr,'(a1,i0)')'_',worldrank write(rankStr,'(a1,i0)')'_',worldrank
fileReadID = HDF5_openFile(trim(getSolverJobName())//trim(rankStr)//'.hdf5') fileReadID = HDF5_openFile(trim(getSolverJobName())//trim(rankStr)//'.hdf5')
allocate(dummy3(size(material_phase,1),size(material_phase,2),size(material_phase,3))) call HDF5_read(crystallite_F0,fileReadID,'convergedF')
call HDF5_readDataSet(fileReadID,'recordedPhase',dummy3,int(shape(material_phase),pLongInt)) call HDF5_read(crystallite_F0,fileReadID,'convergedFp')
material_phase = dummy3 call HDF5_read(crystallite_F0,fileReadID,'convergedFi')
deallocate(dummy3) call HDF5_read(crystallite_F0,fileReadID,'convergedLp')
call HDF5_read(crystallite_F0,fileReadID,'convergedLi')
allocate(dummy5(size(crystallite_F0,1),size(crystallite_F0,2),size(crystallite_F0,3), &
size(crystallite_F0,4),size(crystallite_F0,5)))
call HDF5_readDataSet(fileReadID,'convergedF',dummy5,int(shape(crystallite_F0),pLongInt))
crystallite_F0 = dummy5
deallocate(dummy5)
! call HDF5_readDataSet(fileReadID,'convergedF')
! call HDF5_readDataSet(fileReadID,'convergedFp')
! call HDF5_readDataSet(fileReadID,'convergedFi')
! call HDF5_readDataSet(fileReadID,'convergedLp')
! call HDF5_readDataSet(fileReadID,'convergedLi')
! call HDF5_readDataSet(fileReadID,'convergeddPdF') ! call HDF5_readDataSet(fileReadID,'convergeddPdF')
! call HDF5_readDataSet(fileReadID,'convergedTstar') ! call HDF5_readDataSet(fileReadID,'convergedTstar')
@ -285,8 +270,8 @@ subroutine CPFEM_age()
HDF5_closeFile, & HDF5_closeFile, &
HDF5_closeGroup, & HDF5_closeGroup, &
HDF5_addGroup2, & HDF5_addGroup2, &
HDF5_writeScalarDataset3, & HDF5_writeScalarDataset3
HDF5_addScalarDataset2 !HDF5_addScalarDataset2
use hdf5 use hdf5
use DAMASK_interface, only: & use DAMASK_interface, only: &
getSolverJobName getSolverJobName

View File

@ -10,6 +10,11 @@ module HDF5_Utilities
integer(HID_T), private :: resultsFile, currentIncID, plist_id integer(HID_T), private :: resultsFile, currentIncID, plist_id
integer(pInt), private :: currentInc integer(pInt), private :: currentInc
interface HDF5_read
module procedure HDF5_read_double_1
module procedure HDF5_read_double_5
end interface HDF5_read
public :: & public :: &
HDF5_Utilities_init, & HDF5_Utilities_init, &
HDF5_mappingPhase, & HDF5_mappingPhase, &
@ -31,9 +36,9 @@ module HDF5_Utilities
HDF5_removeLink, & HDF5_removeLink, &
HDF5_createFile, & HDF5_createFile, &
HDF5_closeFile, & HDF5_closeFile, &
HDF5_addGroup2, HDF5_addScalarDataset2, HDF5_writeScalarDataset3, & HDF5_writeScalarDataset3, &
HDF5_openFile, & HDF5_addGroup2, HDF5_read, &
HDF5_readDataSet HDF5_openFile
contains contains
subroutine HDF5_Utilities_init subroutine HDF5_Utilities_init
@ -1334,7 +1339,7 @@ subroutine HDF5_writeScalarDataset(group,dataset,label,SIunit,dataspace_size,mpi
integer(HID_T) :: dset_id, space_id, memspace, plist_id integer(HID_T) :: dset_id, space_id, memspace, plist_id
integer(HSIZE_T), dimension(1) :: counter integer(HSIZE_T), dimension(1) :: counter
integer(HSSIZE_T), dimension(1) :: fileOffset integer(HSIZE_T), dimension(1) :: fileOffset
nNodes = size(dataset) nNodes = size(dataset)
if (nNodes < 1) return if (nNodes < 1) return
@ -1452,24 +1457,62 @@ end subroutine HDF5_writeScalarDataset3
! end subroutine HDF5_writeScalarDatasetLoop ! end subroutine HDF5_writeScalarDatasetLoop
subroutine HDF5_read_double_1(D,ID,label)
implicit none
real(pReal), dimension(:), intent(out) :: D
integer(HID_T), intent(in) :: ID
character(len=*), intent(in) :: label
call HDF5_read_double_generic(D,ID,label,shape(D))
end subroutine HDF5_read_double_1
subroutine HDF5_read_double_5(D,ID,label)
implicit none
real(pReal), dimension(:,:,:,:,:), intent(out) :: D
integer(HID_T), intent(in) :: ID
character(len=*), intent(in) :: label
call HDF5_read_double_generic(D,ID,label,shape(D))
end subroutine HDF5_read_double_5
subroutine HDF5_read_double_generic(D,ID,label,myShape)
use hdf5
implicit none
real(pReal), dimension(*), intent(out) :: D
integer, dimension(:),intent(in) :: myShape
! real, dimension(:), allocatable :: D1
! real, dimension(:,:), allocatable :: D2
! real, dimension(:,:,:), allocatable :: D3
integer(HID_T), intent(in) :: ID
character(len=*), intent(in) :: label
integer(HID_T) :: dset_id
integer :: hdferr
call h5dopen_f(ID,label,dset_id,hdferr)
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,D,int(myshape,HID_T),hdferr)
end subroutine
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief read datasets from a hdf5 file !> @brief read datasets from a hdf5 file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine HDF5_readDataSet(FileReadID,NameDataSet,DataSet,myshape) !
use hdf5 !subroutine HDF5_read_double_2(DataSet,FileReadID,NameDataSet) !,myshape)
! use hdf5
implicit none !
integer(HID_T), intent(in) :: FileReadID ! implicit none
character(len=*), intent(in) :: NameDataSet ! integer(HID_T), intent(in) :: FileReadID
real(pReal), intent(inout), dimension(*) :: DataSet ! character(len=*), intent(in) :: NameDataSet
integer(HSIZE_T), intent(in), dimension(:) :: myshape ! real(pReal), intent(out), dimension(:,:,:,:,:) :: DataSet
integer(HID_T) :: dset_id ! !integer(HSIZE_T), intent(in), dimension(:) :: myshape
integer :: hdferr ! integer(HSIZE_T), dimension(:),allocatable :: myshape
! integer(HID_T) :: dset_id
call h5dopen_f(FileReadID,NameDataSet,dset_id,hdferr) ! integer :: hdferr
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,DataSet,myshape,hdferr) !
! myShape = int(shape(DataSet),HSIZE_T)
end subroutine HDF5_readDataSet ! call h5dopen_f(FileReadID,NameDataSet,dset_id,hdferr)
! call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,DataSet,myshape,hdferr)
!
!end subroutine
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief creates a new scalar dataset in the given group location !> @brief creates a new scalar dataset in the given group location