Merge branch 'polishing' into 'development'
Polishing See merge request damask/DAMASK!601
This commit is contained in:
commit
ac626db9df
2
PRIVATE
2
PRIVATE
|
@ -1 +1 @@
|
|||
Subproject commit 226d7b627e44247b800bce0d9eb7bef1aac6f537
|
||||
Subproject commit b14f78e96a8e2986aaf6845b98ea77fec92bc997
|
|
@ -0,0 +1,15 @@
|
|||
type: dislotwin
|
||||
|
||||
references:
|
||||
- N. Jia et al.,
|
||||
Acta Materialia 60(3):1099-1115, 2012,
|
||||
https://doi.org/10.1016/j.actamat.2011.10.047
|
||||
- N. Jia et al.,
|
||||
Acta Materialia 60:3415-3434, 2012,
|
||||
https://doi.org/10.1016/j.actamat.2012.03.005
|
||||
|
||||
gamma_0_sb: 0.0001
|
||||
tau_sb: 180.0e6 # tau_hat_sb
|
||||
Q_sb: 4.0e-19 # Q_0
|
||||
p_sb: 1.15
|
||||
q_sb: 1.0
|
|
@ -9,6 +9,7 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
submodule(phase:plastic) dislotwin
|
||||
|
||||
real(pReal), parameter :: gamma_char_tr = sqrt(0.125_pReal) !< Characteristic shear for transformation
|
||||
type :: tParameters
|
||||
real(pReal) :: &
|
||||
Q_cl = 1.0_pReal, & !< activation energy for dislocation climb
|
||||
|
@ -22,11 +23,10 @@ submodule(phase:plastic) dislotwin
|
|||
L_tr = 1.0_pReal, & !< length of trans nuclei
|
||||
x_c = 1.0_pReal, & !< critical distance for formation of twin/trans nucleus
|
||||
V_cs = 1.0_pReal, & !< cross slip volume
|
||||
xi_sb = 1.0_pReal, & !< value for shearband resistance
|
||||
v_sb = 1.0_pReal, & !< value for shearband velocity_0
|
||||
tau_sb = 1.0_pReal, & !< value for shearband resistance
|
||||
gamma_0_sb = 1.0_pReal, & !< value for shearband velocity_0
|
||||
E_sb = 1.0_pReal, & !< activation energy for shear bands
|
||||
h = 1.0_pReal, & !< stack height of hex nucleus
|
||||
gamma_char_tr = sqrt(0.125_pReal), & !< Characteristic shear for transformation
|
||||
a_cF = 1.0_pReal, &
|
||||
cOverA_hP = 1.0_pReal, &
|
||||
V_mol = 1.0_pReal, &
|
||||
|
@ -331,15 +331,15 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
|||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! shearband related parameters
|
||||
prm%v_sb = pl%get_asFloat('v_sb',defaultVal=0.0_pReal)
|
||||
if (prm%v_sb > 0.0_pReal) then
|
||||
prm%xi_sb = pl%get_asFloat('xi_sb')
|
||||
prm%gamma_0_sb = pl%get_asFloat('gamma_0_sb',defaultVal=0.0_pReal)
|
||||
if (prm%gamma_0_sb > 0.0_pReal) then
|
||||
prm%tau_sb = pl%get_asFloat('tau_sb')
|
||||
prm%E_sb = pl%get_asFloat('Q_sb')
|
||||
prm%p_sb = pl%get_asFloat('p_sb')
|
||||
prm%q_sb = pl%get_asFloat('q_sb')
|
||||
|
||||
! sanity checks
|
||||
if (prm%xi_sb < 0.0_pReal) extmsg = trim(extmsg)//' xi_sb'
|
||||
if (prm%tau_sb < 0.0_pReal) extmsg = trim(extmsg)//' tau_sb'
|
||||
if (prm%E_sb < 0.0_pReal) extmsg = trim(extmsg)//' Q_sb'
|
||||
if (prm%p_sb <= 0.0_pReal) extmsg = trim(extmsg)//' p_sb'
|
||||
if (prm%q_sb <= 0.0_pReal) extmsg = trim(extmsg)//' q_sb'
|
||||
|
@ -569,7 +569,7 @@ module subroutine dislotwin_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,en)
|
|||
Lp = Lp * f_matrix
|
||||
dLp_dMp = dLp_dMp * f_matrix
|
||||
|
||||
shearBandingContribution: if (dNeq0(prm%v_sb)) then
|
||||
shearBandingContribution: if (dNeq0(prm%gamma_0_sb)) then
|
||||
|
||||
E_kB_T = prm%E_sb/(K_B*T)
|
||||
call math_eigh33(eigValues,eigVectors,Mp) ! is Mp symmetric by design?
|
||||
|
@ -580,10 +580,10 @@ module subroutine dislotwin_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,en)
|
|||
tau = math_tensordot(Mp,P_sb)
|
||||
|
||||
significantShearBandStress: if (abs(tau) > tol_math_check) then
|
||||
StressRatio_p = (abs(tau)/prm%xi_sb)**prm%p_sb
|
||||
dot_gamma_sb = sign(prm%v_sb*exp(-E_kB_T*(1-StressRatio_p)**prm%q_sb), tau)
|
||||
ddot_gamma_dtau = abs(dot_gamma_sb)*E_kB_T*prm%p_sb*prm%q_sb/prm%xi_sb &
|
||||
* (abs(tau)/prm%xi_sb)**(prm%p_sb-1.0_pReal) &
|
||||
StressRatio_p = (abs(tau)/prm%tau_sb)**prm%p_sb
|
||||
dot_gamma_sb = sign(prm%gamma_0_sb*exp(-E_kB_T*(1-StressRatio_p)**prm%q_sb), tau)
|
||||
ddot_gamma_dtau = abs(dot_gamma_sb)*E_kB_T*prm%p_sb*prm%q_sb/prm%tau_sb &
|
||||
* (abs(tau)/prm%tau_sb)**(prm%p_sb-1.0_pReal) &
|
||||
* (1.0_pReal-StressRatio_p)**(prm%q_sb-1.0_pReal)
|
||||
|
||||
Lp = Lp + dot_gamma_sb * P_sb
|
||||
|
@ -697,7 +697,7 @@ module function dislotwin_dotState(Mp,ph,en) result(dotState)
|
|||
dot_f_tw = f_matrix*dot_gamma_tw/prm%gamma_char_tw
|
||||
|
||||
if (prm%sum_N_tr > 0) call kinetics_tr(Mp,T,abs_dot_gamma_sl,ph,en,dot_gamma_tr)
|
||||
dot_f_tr = f_matrix*dot_gamma_tr/prm%gamma_char_tr
|
||||
dot_f_tr = f_matrix*dot_gamma_tr/gamma_char_tr
|
||||
|
||||
end associate
|
||||
|
||||
|
@ -1026,9 +1026,9 @@ pure subroutine kinetics_tr(Mp,T,abs_dot_gamma_sl,ph,en,&
|
|||
dP_ncs_dtau = prm%V_cs / (K_B * T) * (P_ncs - 1.0_pReal)
|
||||
|
||||
V = PI/4.0_pReal*dst%Lambda_tr(i,en)**2*prm%t_tr(i)
|
||||
dot_gamma_tr(i) = V*dot_N_0*P_ncs*P*prm%gamma_char_tr
|
||||
dot_gamma_tr(i) = V*dot_N_0*P_ncs*P*gamma_char_tr
|
||||
if (present(ddot_gamma_dtau_tr)) &
|
||||
ddot_gamma_dtau_tr(i) = V*dot_N_0*(P*dP_ncs_dtau + P_ncs*dP_dtau)*prm%gamma_char_tr
|
||||
ddot_gamma_dtau_tr(i) = V*dot_N_0*(P*dP_ncs_dtau + P_ncs*dP_dtau)*gamma_char_tr
|
||||
else
|
||||
dot_gamma_tr(i) = 0.0_pReal
|
||||
if (present(ddot_gamma_dtau_tr)) ddot_gamma_dtau_tr(i) = 0.0_pReal
|
||||
|
|
120
src/results.f90
120
src/results.f90
|
@ -95,11 +95,11 @@ subroutine results_init(restart)
|
|||
call results_openJobFile
|
||||
call get_command(commandLine)
|
||||
call results_addAttribute('call (restart at '//date//')',trim(commandLine))
|
||||
call h5gmove_f(resultsFile,'setup','tmp',hdferr)
|
||||
call H5Gmove_f(resultsFile,'setup','tmp',hdferr)
|
||||
call results_addAttribute('description','input data used to run the simulation up to restart at '//date,'tmp')
|
||||
call results_closeGroup(results_addGroup('setup'))
|
||||
call results_addAttribute('description','input data used to run the simulation','setup')
|
||||
call h5gmove_f(resultsFile,'tmp','setup/previous',hdferr)
|
||||
call H5Gmove_f(resultsFile,'tmp','setup/previous',hdferr)
|
||||
end if
|
||||
|
||||
call results_closeJobFile
|
||||
|
@ -333,8 +333,8 @@ subroutine results_removeLink(link)
|
|||
integer :: hdferr
|
||||
|
||||
|
||||
call h5ldelete_f(resultsFile,link, hdferr)
|
||||
if (hdferr < 0) call IO_error(1,ext_msg = 'results_removeLink: h5ldelete_soft_f ('//trim(link)//')')
|
||||
call H5Ldelete_f(resultsFile,link, hdferr)
|
||||
if (hdferr < 0) call IO_error(1,ext_msg = 'results_removeLink: H5Ldelete_soft_f ('//trim(link)//')')
|
||||
|
||||
end subroutine results_removeLink
|
||||
|
||||
|
@ -522,7 +522,7 @@ subroutine results_mapping_phase(ID,entry,label)
|
|||
writeSize = 0
|
||||
writeSize(worldrank) = size(entry(1,:)) ! total number of entries of this process
|
||||
|
||||
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
||||
call H5Pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
#ifndef PETSC
|
||||
|
@ -530,7 +530,7 @@ subroutine results_mapping_phase(ID,entry,label)
|
|||
#else
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! MPI settings and communication
|
||||
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
||||
call H5Pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call MPI_Allreduce(MPI_IN_PLACE,writeSize,worldsize,MPI_INTEGER,MPI_SUM,MPI_COMM_WORLD,err_MPI) ! get output at each process
|
||||
|
@ -558,82 +558,82 @@ subroutine results_mapping_phase(ID,entry,label)
|
|||
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
! compound type: label(ID) + entry
|
||||
call h5tcopy_f(H5T_NATIVE_CHARACTER, dt_id, hdferr)
|
||||
call H5Tcopy_f(H5T_NATIVE_CHARACTER, dt_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tset_size_f(dt_id, int(len(label(1)),SIZE_T), hdferr)
|
||||
call H5Tset_size_f(dt_id, int(len(label(1)),SIZE_T), hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tget_size_f(dt_id, type_size_string, hdferr)
|
||||
call H5Tget_size_f(dt_id, type_size_string, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
pI64_t = h5kind_to_type(kind(entryGlobal),H5_INTEGER_KIND)
|
||||
call h5tget_size_f(pI64_t, type_size_int, hdferr)
|
||||
call H5Tget_size_f(pI64_t, type_size_int, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5tcreate_f(H5T_COMPOUND_F, type_size_string + type_size_int, dtype_id, hdferr)
|
||||
call H5Tcreate_f(H5T_COMPOUND_F, type_size_string + type_size_int, dtype_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(dtype_id, 'label', 0_SIZE_T, dt_id,hdferr)
|
||||
call H5Tinsert_f(dtype_id, 'label', 0_SIZE_T, dt_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(dtype_id, 'entry', type_size_string, pI64_t, hdferr)
|
||||
call H5Tinsert_f(dtype_id, 'entry', type_size_string, pI64_t, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! create memory types for each component of the compound type
|
||||
call h5tcreate_f(H5T_COMPOUND_F, type_size_string, label_id, hdferr)
|
||||
call H5Tcreate_f(H5T_COMPOUND_F, type_size_string, label_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(label_id, 'label', 0_SIZE_T, dt_id, hdferr)
|
||||
call H5Tinsert_f(label_id, 'label', 0_SIZE_T, dt_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5tcreate_f(H5T_COMPOUND_F, type_size_int, entry_id, hdferr)
|
||||
call H5Tcreate_f(H5T_COMPOUND_F, type_size_int, entry_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(entry_id, 'entry', 0_SIZE_T, pI64_t, hdferr)
|
||||
call H5Tinsert_f(entry_id, 'entry', 0_SIZE_T, pI64_t, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5tclose_f(dt_id, hdferr)
|
||||
call H5Tclose_f(dt_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! create dataspace in memory (local shape = hyperslab) and in file (global shape)
|
||||
call h5screate_simple_f(2,myShape,memspace_id,hdferr,myShape)
|
||||
call H5Screate_simple_f(2,myShape,memspace_id,hdferr,myShape)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5screate_simple_f(2,totalShape,filespace_id,hdferr,totalShape)
|
||||
call H5Screate_simple_f(2,totalShape,filespace_id,hdferr,totalShape)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myOffset, myShape, hdferr)
|
||||
call H5Sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myOffset, myShape, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! write the components of the compound type individually
|
||||
call h5pset_preserve_f(plist_id, .true., hdferr)
|
||||
call H5Pset_preserve_f(plist_id, .true., hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
loc_id = results_openGroup('/cell_to')
|
||||
call h5dcreate_f(loc_id, 'phase', dtype_id, filespace_id, dset_id, hdferr)
|
||||
call H5Dcreate_f(loc_id, 'phase', dtype_id, filespace_id, dset_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5dwrite_f(dset_id, label_id, reshape(label(pack(ID,.true.)),myShape), &
|
||||
call H5Dwrite_f(dset_id, label_id, reshape(label(pack(ID,.true.)),myShape), &
|
||||
myShape, hdferr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5dwrite_f(dset_id, entry_id, reshape(pack(entryGlobal,.true.),myShape), &
|
||||
call H5Dwrite_f(dset_id, entry_id, reshape(pack(entryGlobal,.true.),myShape), &
|
||||
myShape, hdferr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! close all
|
||||
call HDF5_closeGroup(loc_id)
|
||||
call h5pclose_f(plist_id, hdferr)
|
||||
call H5Pclose_f(plist_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5sclose_f(filespace_id, hdferr)
|
||||
call H5Sclose_f(filespace_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5sclose_f(memspace_id, hdferr)
|
||||
call H5Sclose_f(memspace_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5dclose_f(dset_id, hdferr)
|
||||
call H5Dclose_f(dset_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(dtype_id, hdferr)
|
||||
call H5Tclose_f(dtype_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(label_id, hdferr)
|
||||
call H5Tclose_f(label_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(entry_id, hdferr)
|
||||
call H5Tclose_f(entry_id, hdferr)
|
||||
|
||||
call executionStamp('cell_to/phase','cell ID and constituent ID to phase results')
|
||||
|
||||
|
@ -678,7 +678,7 @@ subroutine results_mapping_homogenization(ID,entry,label)
|
|||
writeSize = 0
|
||||
writeSize(worldrank) = size(entry) ! total number of entries of this process
|
||||
|
||||
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
||||
call H5Pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
#ifndef PETSC
|
||||
|
@ -686,7 +686,7 @@ subroutine results_mapping_homogenization(ID,entry,label)
|
|||
#else
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! MPI settings and communication
|
||||
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
||||
call H5Pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call MPI_Allreduce(MPI_IN_PLACE,writeSize,worldsize,MPI_INTEGER,MPI_SUM,MPI_COMM_WORLD,err_MPI) ! get output at each process
|
||||
|
@ -710,82 +710,82 @@ subroutine results_mapping_homogenization(ID,entry,label)
|
|||
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
! compound type: label(ID) + entry
|
||||
call h5tcopy_f(H5T_NATIVE_CHARACTER, dt_id, hdferr)
|
||||
call H5Tcopy_f(H5T_NATIVE_CHARACTER, dt_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tset_size_f(dt_id, int(len(label(1)),SIZE_T), hdferr)
|
||||
call H5Tset_size_f(dt_id, int(len(label(1)),SIZE_T), hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tget_size_f(dt_id, type_size_string, hdferr)
|
||||
call H5Tget_size_f(dt_id, type_size_string, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
pI64_t = h5kind_to_type(kind(entryGlobal),H5_INTEGER_KIND)
|
||||
call h5tget_size_f(pI64_t, type_size_int, hdferr)
|
||||
call H5Tget_size_f(pI64_t, type_size_int, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5tcreate_f(H5T_COMPOUND_F, type_size_string + type_size_int, dtype_id, hdferr)
|
||||
call H5Tcreate_f(H5T_COMPOUND_F, type_size_string + type_size_int, dtype_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(dtype_id, 'label', 0_SIZE_T, dt_id,hdferr)
|
||||
call H5Tinsert_f(dtype_id, 'label', 0_SIZE_T, dt_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(dtype_id, 'entry', type_size_string, pI64_t, hdferr)
|
||||
call H5Tinsert_f(dtype_id, 'entry', type_size_string, pI64_t, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! create memory types for each component of the compound type
|
||||
call h5tcreate_f(H5T_COMPOUND_F, type_size_string, label_id, hdferr)
|
||||
call H5Tcreate_f(H5T_COMPOUND_F, type_size_string, label_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(label_id, 'label', 0_SIZE_T, dt_id, hdferr)
|
||||
call H5Tinsert_f(label_id, 'label', 0_SIZE_T, dt_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5tcreate_f(H5T_COMPOUND_F, type_size_int, entry_id, hdferr)
|
||||
call H5Tcreate_f(H5T_COMPOUND_F, type_size_int, entry_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tinsert_f(entry_id, 'entry', 0_SIZE_T, pI64_t, hdferr)
|
||||
call H5Tinsert_f(entry_id, 'entry', 0_SIZE_T, pI64_t, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5tclose_f(dt_id, hdferr)
|
||||
call H5Tclose_f(dt_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! create dataspace in memory (local shape = hyperslab) and in file (global shape)
|
||||
call h5screate_simple_f(1,myShape,memspace_id,hdferr,myShape)
|
||||
call H5Screate_simple_f(1,myShape,memspace_id,hdferr,myShape)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5screate_simple_f(1,totalShape,filespace_id,hdferr,totalShape)
|
||||
call H5Screate_simple_f(1,totalShape,filespace_id,hdferr,totalShape)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myOffset, myShape, hdferr)
|
||||
call H5Sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myOffset, myShape, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! write the components of the compound type individually
|
||||
call h5pset_preserve_f(plist_id, .true., hdferr)
|
||||
call H5Pset_preserve_f(plist_id, .true., hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
loc_id = results_openGroup('/cell_to')
|
||||
call h5dcreate_f(loc_id, 'homogenization', dtype_id, filespace_id, dset_id, hdferr)
|
||||
call H5Dcreate_f(loc_id, 'homogenization', dtype_id, filespace_id, dset_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5dwrite_f(dset_id, label_id, reshape(label(pack(ID,.true.)),myShape), &
|
||||
call H5Dwrite_f(dset_id, label_id, reshape(label(pack(ID,.true.)),myShape), &
|
||||
myShape, hdferr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5dwrite_f(dset_id, entry_id, reshape(pack(entryGlobal,.true.),myShape), &
|
||||
call H5Dwrite_f(dset_id, entry_id, reshape(pack(entryGlobal,.true.),myShape), &
|
||||
myShape, hdferr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! close all
|
||||
call HDF5_closeGroup(loc_id)
|
||||
call h5pclose_f(plist_id, hdferr)
|
||||
call H5Pclose_f(plist_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5sclose_f(filespace_id, hdferr)
|
||||
call H5Sclose_f(filespace_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5sclose_f(memspace_id, hdferr)
|
||||
call H5Sclose_f(memspace_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5dclose_f(dset_id, hdferr)
|
||||
call H5Dclose_f(dset_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(dtype_id, hdferr)
|
||||
call H5Tclose_f(dtype_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(label_id, hdferr)
|
||||
call H5Tclose_f(label_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(entry_id, hdferr)
|
||||
call H5Tclose_f(entry_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call executionStamp('cell_to/homogenization','cell ID to homogenization results')
|
||||
|
|
Loading…
Reference in New Issue