Reading and writing not very efficient method
This commit is contained in:
parent
8619b49e20
commit
a6ebdfc1ff
|
@ -91,7 +91,7 @@ subroutine CPFEM_init
|
||||||
compiler_options
|
compiler_options
|
||||||
#endif
|
#endif
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pInt, pReal
|
pInt, pReal, pLongInt
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_read_realFile,&
|
IO_read_realFile,&
|
||||||
IO_read_intFile, &
|
IO_read_intFile, &
|
||||||
|
@ -122,11 +122,23 @@ subroutine CPFEM_init
|
||||||
crystallite_Li0, &
|
crystallite_Li0, &
|
||||||
crystallite_dPdF0, &
|
crystallite_dPdF0, &
|
||||||
crystallite_Tstar0_v
|
crystallite_Tstar0_v
|
||||||
|
use hdf5
|
||||||
|
use HDF5_utilities, only: &
|
||||||
|
HDF5_openFile, &
|
||||||
|
HDF5_openGroup2, &
|
||||||
|
HDF5_readDataSet
|
||||||
|
use DAMASK_interface, only: &
|
||||||
|
getSolverJobName
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt) :: k,l,m,ph,homog
|
integer(pInt) :: k,l,m,ph,homog
|
||||||
character(len=1024) :: rankStr
|
character(len=1024) :: rankStr
|
||||||
|
integer(HID_T) :: fileReadID, groupPlasticID
|
||||||
|
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 -+>>>'
|
||||||
|
@ -134,16 +146,40 @@ 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 binary files'
|
||||||
|
write(6,'(a)') '<< CPFEM >> restored state variables of last converged step from hdf5 file'
|
||||||
flush(6)
|
flush(6)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
write(rankStr,'(a1,i0)')'_',worldrank
|
||||||
|
|
||||||
|
fileReadID = HDF5_openFile(trim(getSolverJobName())//trim(rankStr)//'.hdf5')
|
||||||
|
|
||||||
|
allocate(dummy3(size(material_phase,1),size(material_phase,2),size(material_phase,3)))
|
||||||
|
call HDF5_readDataSet(fileReadID,'recordedPhase',dummy3,int(shape(material_phase),pLongInt))
|
||||||
|
material_phase = dummy3
|
||||||
|
deallocate(dummy3)
|
||||||
|
|
||||||
|
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,'convergedTstar')
|
||||||
|
|
||||||
|
! groupPlasticID = HDF5_openGroup2(fileReadID,'PlasticPhases')
|
||||||
|
! call HDF5_readDataSet(groupPlasticID,'convergedStateConst')
|
||||||
|
|
||||||
call IO_read_intFile(777,'recordedPhase'//trim(rankStr),modelName,size(material_phase))
|
call IO_read_intFile(777,'recordedPhase'//trim(rankStr),modelName,size(material_phase))
|
||||||
read (777,rec=1) material_phase; close (777)
|
read (777,rec=1) material_phase; close (777)
|
||||||
|
|
||||||
|
@ -259,7 +295,7 @@ subroutine CPFEM_age()
|
||||||
|
|
||||||
integer(pInt) :: i, k, l, m, ph, homog, mySource
|
integer(pInt) :: i, k, l, m, ph, homog, mySource
|
||||||
character(len=32) :: rankStr
|
character(len=32) :: rankStr
|
||||||
integer(HID_T) :: fileHandle, groupHandle
|
integer(HID_T) :: fileHandle, groupPlastic, groupHomog
|
||||||
integer :: hdferr
|
integer :: hdferr
|
||||||
integer(HSIZE_T) :: hdfsize
|
integer(HSIZE_T) :: hdfsize
|
||||||
|
|
||||||
|
@ -310,8 +346,15 @@ if (restartWrite) then
|
||||||
call HDF5_writeScalarDataset3(fileHandle,crystallite_dPdF0,'convergeddPdF',shape(crystallite_dPdF0))
|
call HDF5_writeScalarDataset3(fileHandle,crystallite_dPdF0,'convergeddPdF',shape(crystallite_dPdF0))
|
||||||
call HDF5_writeScalarDataset3(fileHandle,crystallite_Tstar0_v,'convergedTstar',shape(crystallite_Tstar0_v))
|
call HDF5_writeScalarDataset3(fileHandle,crystallite_Tstar0_v,'convergedTstar',shape(crystallite_Tstar0_v))
|
||||||
|
|
||||||
groupHandle = HDF5_addGroup2(fileHandle,'PlasticPhases')
|
groupPlastic = HDF5_addGroup2(fileHandle,'PlasticPhases')
|
||||||
!call HDF5_writeScalarDatasetLoop(fileHandle,plasticState(ph)%state0,'convergedStateConst',shape())
|
do ph = 1_pInt,size(phase_plasticity)
|
||||||
|
call HDF5_writeScalarDataset3(groupPlastic,plasticState(ph)%state0,'convergedStateConst',shape(plasticState(ph)%state0))
|
||||||
|
enddo
|
||||||
|
|
||||||
|
groupHomog = HDF5_addGroup2(fileHandle,'material_Nhomogenization')
|
||||||
|
do homog = 1_pInt, material_Nhomogenization
|
||||||
|
call HDF5_writeScalarDataset3(groupHomog,homogState(homog)%state0,'convergedStateHomog',shape(homogState(homog)%state0))
|
||||||
|
enddo
|
||||||
|
|
||||||
call HDF5_closeFile(fileHandle)
|
call HDF5_closeFile(fileHandle)
|
||||||
|
|
||||||
|
|
|
@ -22,6 +22,7 @@ module HDF5_Utilities
|
||||||
HDF5_addGroup ,&
|
HDF5_addGroup ,&
|
||||||
HDF5_closeGroup ,&
|
HDF5_closeGroup ,&
|
||||||
HDF5_openGroup, &
|
HDF5_openGroup, &
|
||||||
|
HDF5_openGroup2, &
|
||||||
HDF5_forwardResults, &
|
HDF5_forwardResults, &
|
||||||
HDF5_writeVectorDataset, &
|
HDF5_writeVectorDataset, &
|
||||||
HDF5_writeScalarDataset, &
|
HDF5_writeScalarDataset, &
|
||||||
|
@ -30,7 +31,9 @@ module HDF5_Utilities
|
||||||
HDF5_removeLink, &
|
HDF5_removeLink, &
|
||||||
HDF5_createFile, &
|
HDF5_createFile, &
|
||||||
HDF5_closeFile, &
|
HDF5_closeFile, &
|
||||||
HDF5_addGroup2, HDF5_addScalarDataset2, HDF5_writeScalarDataset3
|
HDF5_addGroup2, HDF5_addScalarDataset2, HDF5_writeScalarDataset3, &
|
||||||
|
HDF5_openFile, &
|
||||||
|
HDF5_readDataSet
|
||||||
contains
|
contains
|
||||||
|
|
||||||
subroutine HDF5_Utilities_init
|
subroutine HDF5_Utilities_init
|
||||||
|
@ -146,6 +149,22 @@ subroutine HDF5_closeJobFile()
|
||||||
|
|
||||||
end subroutine HDF5_closeJobFile
|
end subroutine HDF5_closeJobFile
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief open and initializes HDF5 output file
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
integer(HID_T) function HDF5_openFile(filePath)
|
||||||
|
use hdf5
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
integer :: hdferr
|
||||||
|
character(len=*), intent(in) :: filePath
|
||||||
|
|
||||||
|
call h5open_f(hdferr)!############################################################ DANGEROUS
|
||||||
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5open_f',el=hdferr)
|
||||||
|
call h5fopen_f(filePath,H5F_ACC_RDONLY_F,HDF5_openFile,hdferr)
|
||||||
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fopen_f',el=hdferr)
|
||||||
|
|
||||||
|
end function HDF5_openFile
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief creates and initializes HDF5 output file
|
!> @brief creates and initializes HDF5 output file
|
||||||
|
@ -163,7 +182,6 @@ subroutine HDF5_closeFile(fileHandle)
|
||||||
|
|
||||||
end subroutine HDF5_closeFile
|
end subroutine HDF5_closeFile
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief adds a new group to the results file, or if loc is present at the given location
|
!> @brief adds a new group to the results file, or if loc is present at the given location
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -211,6 +229,22 @@ integer(HID_T) function HDF5_openGroup(path)
|
||||||
|
|
||||||
end function HDF5_openGroup
|
end function HDF5_openGroup
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief open a existing group of the results file
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
integer(HID_T) function HDF5_openGroup2(FileReadID,path)
|
||||||
|
use hdf5
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
character(len=*), intent(in) :: path
|
||||||
|
integer :: hdferr
|
||||||
|
integer(HID_T), intent(in) :: FileReadID
|
||||||
|
write(6,*) FileReadID,'hello';flush(6)
|
||||||
|
call h5gopen_f(FileReadID, trim(path), HDF5_openGroup2, hdferr)
|
||||||
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_openGroup2: h5gopen_f ('//trim(path)//')')
|
||||||
|
|
||||||
|
end function HDF5_openGroup2
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief adds a new group to the results file
|
!> @brief adds a new group to the results file
|
||||||
|
@ -1418,6 +1452,25 @@ end subroutine HDF5_writeScalarDataset3
|
||||||
|
|
||||||
! end subroutine HDF5_writeScalarDatasetLoop
|
! end subroutine HDF5_writeScalarDatasetLoop
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief read datasets from a hdf5 file
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
subroutine HDF5_readDataSet(FileReadID,NameDataSet,DataSet,myshape)
|
||||||
|
use hdf5
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
integer(HID_T), intent(in) :: FileReadID
|
||||||
|
character(len=*), intent(in) :: NameDataSet
|
||||||
|
real(pReal), intent(inout), dimension(*) :: DataSet
|
||||||
|
integer(HSIZE_T), intent(in), dimension(:) :: myshape
|
||||||
|
integer(HID_T) :: dset_id
|
||||||
|
integer :: hdferr
|
||||||
|
|
||||||
|
call h5dopen_f(FileReadID,NameDataSet,dset_id,hdferr)
|
||||||
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,DataSet,myshape,hdferr)
|
||||||
|
|
||||||
|
end subroutine HDF5_readDataSet
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief creates a new scalar dataset in the given group location
|
!> @brief creates a new scalar dataset in the given group location
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
Loading…
Reference in New Issue