2016-01-17 20:33:54 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief needs a good name and description
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
module CPFEM2
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
private
|
|
|
|
|
|
|
|
public :: &
|
2018-02-16 20:06:18 +05:30
|
|
|
CPFEM_age, &
|
2018-12-05 04:25:39 +05:30
|
|
|
CPFEM_initAll, &
|
|
|
|
CPFEM_results
|
2016-01-17 20:33:54 +05:30
|
|
|
contains
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief call (thread safe) all module initializations
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-09-24 01:01:30 +05:30
|
|
|
subroutine CPFEM_initAll()
|
2016-01-20 21:49:05 +05:30
|
|
|
use prec, only: &
|
2018-12-05 04:25:39 +05:30
|
|
|
pInt, &
|
2016-01-17 20:33:54 +05:30
|
|
|
prec_init
|
|
|
|
use numerics, only: &
|
|
|
|
numerics_init
|
|
|
|
use debug, only: &
|
|
|
|
debug_init
|
2018-06-14 10:09:49 +05:30
|
|
|
use config, only: &
|
|
|
|
config_init
|
2016-01-17 20:33:54 +05:30
|
|
|
use FEsolving, only: &
|
|
|
|
FE_init
|
|
|
|
use math, only: &
|
|
|
|
math_init
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_init
|
|
|
|
use material, only: &
|
|
|
|
material_init
|
2018-10-09 17:43:51 +05:30
|
|
|
use HDF5_utilities, only: &
|
|
|
|
HDF5_utilities_init
|
2018-11-18 16:28:49 +05:30
|
|
|
use results, only: &
|
|
|
|
results_init
|
2018-06-03 00:29:30 +05:30
|
|
|
use lattice, only: &
|
|
|
|
lattice_init
|
2016-01-17 20:33:54 +05:30
|
|
|
use constitutive, only: &
|
|
|
|
constitutive_init
|
|
|
|
use crystallite, only: &
|
|
|
|
crystallite_init
|
|
|
|
use homogenization, only: &
|
2016-01-20 21:49:05 +05:30
|
|
|
homogenization_init, &
|
2016-05-27 15:16:34 +05:30
|
|
|
materialpoint_postResults
|
2016-01-17 20:33:54 +05:30
|
|
|
use IO, only: &
|
|
|
|
IO_init
|
|
|
|
use DAMASK_interface
|
|
|
|
#ifdef FEM
|
2018-08-17 14:53:24 +05:30
|
|
|
use FEM_Zoo, only: &
|
|
|
|
FEM_Zoo_init
|
2016-01-17 20:33:54 +05:30
|
|
|
#endif
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
2018-09-24 01:01:30 +05:30
|
|
|
call DAMASK_interface_init ! Spectral and FEM interface to commandline
|
2016-01-20 21:49:05 +05:30
|
|
|
call prec_init
|
|
|
|
call IO_init
|
2016-01-17 20:33:54 +05:30
|
|
|
#ifdef FEM
|
2018-08-17 14:53:24 +05:30
|
|
|
call FEM_Zoo_init
|
2016-01-17 20:33:54 +05:30
|
|
|
#endif
|
2016-01-20 21:49:05 +05:30
|
|
|
call numerics_init
|
|
|
|
call debug_init
|
2018-06-14 10:09:49 +05:30
|
|
|
call config_init
|
2016-01-20 21:49:05 +05:30
|
|
|
call math_init
|
|
|
|
call FE_init
|
2018-09-24 01:01:30 +05:30
|
|
|
call mesh_init
|
2016-01-20 21:49:05 +05:30
|
|
|
call lattice_init
|
2018-10-09 17:43:51 +05:30
|
|
|
call HDF5_utilities_init
|
2018-11-18 16:28:49 +05:30
|
|
|
call results_init
|
2019-04-04 19:52:33 +05:30
|
|
|
call material_init
|
2016-01-20 21:49:05 +05:30
|
|
|
call constitutive_init
|
|
|
|
call crystallite_init
|
|
|
|
call homogenization_init
|
|
|
|
call materialpoint_postResults
|
2016-05-27 15:16:34 +05:30
|
|
|
call CPFEM_init
|
2016-01-17 20:33:54 +05:30
|
|
|
|
|
|
|
end subroutine CPFEM_initAll
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief allocate the arrays defined in module CPFEM and initialize them
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine CPFEM_init
|
|
|
|
use prec, only: &
|
2019-03-06 20:19:31 +05:30
|
|
|
pInt, pReal
|
2016-01-17 20:33:54 +05:30
|
|
|
use IO, only: &
|
|
|
|
IO_error
|
|
|
|
use numerics, only: &
|
|
|
|
worldrank
|
|
|
|
use debug, only: &
|
|
|
|
debug_level, &
|
|
|
|
debug_CPFEM, &
|
|
|
|
debug_levelBasic, &
|
|
|
|
debug_levelExtensive
|
|
|
|
use FEsolving, only: &
|
2018-12-05 03:39:25 +05:30
|
|
|
restartRead
|
2016-01-17 20:33:54 +05:30
|
|
|
use material, only: &
|
|
|
|
material_phase, &
|
|
|
|
homogState, &
|
|
|
|
phase_plasticity, &
|
2018-06-10 21:31:52 +05:30
|
|
|
plasticState
|
2018-06-14 10:09:49 +05:30
|
|
|
use config, only: &
|
2016-01-17 20:33:54 +05:30
|
|
|
material_Nhomogenization
|
|
|
|
use crystallite, only: &
|
|
|
|
crystallite_F0, &
|
|
|
|
crystallite_Fp0, &
|
|
|
|
crystallite_Lp0, &
|
|
|
|
crystallite_Fi0, &
|
|
|
|
crystallite_Li0, &
|
2019-03-09 05:03:11 +05:30
|
|
|
crystallite_S0
|
2018-10-04 20:30:24 +05:30
|
|
|
use hdf5
|
|
|
|
use HDF5_utilities, only: &
|
|
|
|
HDF5_openFile, &
|
2018-12-05 03:39:25 +05:30
|
|
|
HDF5_closeFile, &
|
|
|
|
HDF5_openGroup, &
|
|
|
|
HDF5_closeGroup, &
|
2018-10-05 12:26:06 +05:30
|
|
|
HDF5_read
|
2018-10-04 20:30:24 +05:30
|
|
|
use DAMASK_interface, only: &
|
|
|
|
getSolverJobName
|
2016-01-17 20:33:54 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(pInt) :: ph,homog
|
2018-10-11 21:30:01 +05:30
|
|
|
character(len=1024) :: rankStr, PlasticItem, HomogItem
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(HID_T) :: fileHandle, groupPlasticID, groupHomogID
|
2016-01-17 20:33:54 +05:30
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- CPFEM init -+>>>'
|
|
|
|
flush(6)
|
2016-01-17 20:33:54 +05:30
|
|
|
|
|
|
|
! *** restore the last converged values of each essential variable from the binary file
|
|
|
|
if (restartRead) then
|
|
|
|
if (iand(debug_level(debug_CPFEM), debug_levelExtensive) /= 0_pInt) then
|
2018-10-04 20:30:24 +05:30
|
|
|
write(6,'(a)') '<< CPFEM >> restored state variables of last converged step from hdf5 file'
|
2016-01-17 20:33:54 +05:30
|
|
|
flush(6)
|
|
|
|
endif
|
|
|
|
|
|
|
|
write(rankStr,'(a1,i0)')'_',worldrank
|
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
fileHandle = HDF5_openFile(trim(getSolverJobName())//trim(rankStr)//'.hdf5')
|
2018-10-05 12:26:06 +05:30
|
|
|
|
2018-12-17 20:45:16 +05:30
|
|
|
call HDF5_read(fileHandle,material_phase, 'recordedPhase')
|
|
|
|
call HDF5_read(fileHandle,crystallite_F0, 'convergedF')
|
|
|
|
call HDF5_read(fileHandle,crystallite_Fp0, 'convergedFp')
|
|
|
|
call HDF5_read(fileHandle,crystallite_Fi0, 'convergedFi')
|
|
|
|
call HDF5_read(fileHandle,crystallite_Lp0, 'convergedLp')
|
|
|
|
call HDF5_read(fileHandle,crystallite_Li0, 'convergedLi')
|
2019-03-09 05:03:11 +05:30
|
|
|
call HDF5_read(fileHandle,crystallite_S0, 'convergedS')
|
2018-10-04 20:30:24 +05:30
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
groupPlasticID = HDF5_openGroup(fileHandle,'PlasticPhases')
|
2018-10-09 14:27:06 +05:30
|
|
|
do ph = 1_pInt,size(phase_plasticity)
|
2018-10-11 21:30:01 +05:30
|
|
|
write(PlasticItem,*) ph,'_'
|
2018-12-14 16:05:41 +05:30
|
|
|
call HDF5_read(groupPlasticID,plasticState(ph)%state0,trim(PlasticItem)//'convergedStateConst')
|
2018-10-09 14:27:06 +05:30
|
|
|
enddo
|
2018-12-05 03:39:25 +05:30
|
|
|
call HDF5_closeGroup(groupPlasticID)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
groupHomogID = HDF5_openGroup(fileHandle,'HomogStates')
|
2018-10-09 14:27:06 +05:30
|
|
|
do homog = 1_pInt, material_Nhomogenization
|
2018-10-11 21:30:01 +05:30
|
|
|
write(HomogItem,*) homog,'_'
|
2018-12-14 16:05:41 +05:30
|
|
|
call HDF5_read(groupHomogID,homogState(homog)%state0, trim(HomogItem)//'convergedStateHomog')
|
2018-10-09 14:27:06 +05:30
|
|
|
enddo
|
2018-12-05 03:39:25 +05:30
|
|
|
call HDF5_closeGroup(groupHomogID)
|
|
|
|
|
|
|
|
call HDF5_closeFile(fileHandle)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2016-01-17 20:33:54 +05:30
|
|
|
restartRead = .false.
|
|
|
|
endif
|
|
|
|
|
|
|
|
end subroutine CPFEM_init
|
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
|
2016-01-17 20:33:54 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-08-20 20:37:20 +05:30
|
|
|
!> @brief forwards data after successful increment
|
2016-01-17 20:33:54 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-02-16 20:06:18 +05:30
|
|
|
subroutine CPFEM_age()
|
2016-01-20 21:49:05 +05:30
|
|
|
use prec, only: &
|
|
|
|
pReal, &
|
|
|
|
pInt
|
2016-01-17 20:33:54 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank
|
|
|
|
use debug, only: &
|
|
|
|
debug_level, &
|
|
|
|
debug_CPFEM, &
|
|
|
|
debug_levelBasic, &
|
|
|
|
debug_levelExtensive, &
|
|
|
|
debug_levelSelective
|
|
|
|
use FEsolving, only: &
|
|
|
|
restartWrite
|
|
|
|
use material, only: &
|
|
|
|
plasticState, &
|
|
|
|
sourceState, &
|
|
|
|
homogState, &
|
|
|
|
thermalState, &
|
|
|
|
damageState, &
|
|
|
|
material_phase, &
|
|
|
|
phase_plasticity, &
|
2018-06-10 21:31:52 +05:30
|
|
|
phase_Nsources
|
2018-06-14 10:09:49 +05:30
|
|
|
use config, only: &
|
2016-01-17 20:33:54 +05:30
|
|
|
material_Nhomogenization
|
|
|
|
use crystallite, only: &
|
|
|
|
crystallite_partionedF,&
|
|
|
|
crystallite_F0, &
|
|
|
|
crystallite_Fp0, &
|
|
|
|
crystallite_Fp, &
|
|
|
|
crystallite_Fi0, &
|
|
|
|
crystallite_Fi, &
|
|
|
|
crystallite_Lp0, &
|
|
|
|
crystallite_Lp, &
|
|
|
|
crystallite_Li0, &
|
|
|
|
crystallite_Li, &
|
2019-03-09 05:03:11 +05:30
|
|
|
crystallite_S0, &
|
|
|
|
crystallite_S
|
2018-09-20 23:12:58 +05:30
|
|
|
use HDF5_utilities, only: &
|
2018-10-09 19:42:32 +05:30
|
|
|
HDF5_openFile, &
|
2018-09-20 23:12:58 +05:30
|
|
|
HDF5_closeFile, &
|
2018-12-05 03:39:25 +05:30
|
|
|
HDF5_addGroup, &
|
2018-09-20 23:12:58 +05:30
|
|
|
HDF5_closeGroup, &
|
2018-10-09 14:27:06 +05:30
|
|
|
HDF5_write
|
2018-09-25 20:12:43 +05:30
|
|
|
use hdf5
|
2018-09-20 23:12:58 +05:30
|
|
|
use DAMASK_interface, only: &
|
|
|
|
getSolverJobName
|
2016-01-17 20:33:54 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(pInt) :: i, ph, homog, mySource
|
2018-10-10 22:38:44 +05:30
|
|
|
character(len=32) :: rankStr, PlasticItem, HomogItem
|
2018-10-04 20:30:24 +05:30
|
|
|
integer(HID_T) :: fileHandle, groupPlastic, groupHomog
|
2018-02-16 20:06:18 +05:30
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt) &
|
|
|
|
write(6,'(a)') '<< CPFEM >> aging states'
|
2018-02-16 20:06:18 +05:30
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
crystallite_F0 = crystallite_partionedF
|
|
|
|
crystallite_Fp0 = crystallite_Fp
|
|
|
|
crystallite_Lp0 = crystallite_Lp
|
|
|
|
crystallite_Fi0 = crystallite_Fi
|
|
|
|
crystallite_Li0 = crystallite_Li
|
2019-03-09 05:03:11 +05:30
|
|
|
crystallite_S0 = crystallite_S
|
2019-03-10 14:10:20 +05:30
|
|
|
|
|
|
|
do i = 1, size(plasticState)
|
|
|
|
plasticState(i)%state0 = plasticState(i)%state
|
|
|
|
enddo
|
2018-12-05 04:25:39 +05:30
|
|
|
do i = 1, size(sourceState)
|
|
|
|
do mySource = 1,phase_Nsources(i)
|
2019-03-10 14:10:20 +05:30
|
|
|
sourceState(i)%p(mySource)%state0 = sourceState(i)%p(mySource)%state
|
2018-12-05 04:25:39 +05:30
|
|
|
enddo; enddo
|
|
|
|
do homog = 1_pInt, material_Nhomogenization
|
|
|
|
homogState (homog)%state0 = homogState (homog)%state
|
|
|
|
thermalState (homog)%state0 = thermalState (homog)%state
|
|
|
|
damageState (homog)%state0 = damageState (homog)%state
|
|
|
|
enddo
|
2018-02-16 20:06:18 +05:30
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
if (restartWrite) then
|
|
|
|
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt) &
|
|
|
|
write(6,'(a)') '<< CPFEM >> writing restart variables of last converged step to hdf5 file'
|
|
|
|
|
|
|
|
write(rankStr,'(a1,i0)')'_',worldrank
|
2019-04-10 16:53:57 +05:30
|
|
|
fileHandle = HDF5_openFile(trim(getSolverJobName())//trim(rankStr)//'.hdf5','a')
|
2018-12-05 04:25:39 +05:30
|
|
|
|
2018-12-17 20:45:16 +05:30
|
|
|
call HDF5_write(fileHandle,material_phase, 'recordedPhase')
|
|
|
|
call HDF5_write(fileHandle,crystallite_F0, 'convergedF')
|
|
|
|
call HDF5_write(fileHandle,crystallite_Fp0, 'convergedFp')
|
|
|
|
call HDF5_write(fileHandle,crystallite_Fi0, 'convergedFi')
|
|
|
|
call HDF5_write(fileHandle,crystallite_Lp0, 'convergedLp')
|
|
|
|
call HDF5_write(fileHandle,crystallite_Li0, 'convergedLi')
|
2019-03-09 05:03:11 +05:30
|
|
|
call HDF5_write(fileHandle,crystallite_S0, 'convergedS')
|
2018-12-05 04:25:39 +05:30
|
|
|
|
|
|
|
groupPlastic = HDF5_addGroup(fileHandle,'PlasticPhases')
|
|
|
|
do ph = 1_pInt,size(phase_plasticity)
|
|
|
|
write(PlasticItem,*) ph,'_'
|
2018-12-14 16:05:41 +05:30
|
|
|
call HDF5_write(groupPlastic,plasticState(ph)%state0,trim(PlasticItem)//'convergedStateConst')
|
2018-12-05 04:25:39 +05:30
|
|
|
enddo
|
|
|
|
call HDF5_closeGroup(groupPlastic)
|
2018-10-09 19:42:32 +05:30
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
groupHomog = HDF5_addGroup(fileHandle,'HomogStates')
|
|
|
|
do homog = 1_pInt, material_Nhomogenization
|
|
|
|
write(HomogItem,*) homog,'_'
|
2018-12-14 16:05:41 +05:30
|
|
|
call HDF5_write(groupHomog,homogState(homog)%state0,trim(HomogItem)//'convergedStateHomog')
|
2018-12-05 04:25:39 +05:30
|
|
|
enddo
|
|
|
|
call HDF5_closeGroup(groupHomog)
|
|
|
|
|
|
|
|
call HDF5_closeFile(fileHandle)
|
|
|
|
restartWrite = .false.
|
|
|
|
endif
|
2018-02-16 20:06:18 +05:30
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt) &
|
|
|
|
write(6,'(a)') '<< CPFEM >> done aging states'
|
2018-02-16 20:06:18 +05:30
|
|
|
|
|
|
|
end subroutine CPFEM_age
|
2016-01-17 20:33:54 +05:30
|
|
|
|
2018-12-05 04:25:39 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief triggers writing of the results
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
subroutine CPFEM_results(inc,time)
|
2018-12-05 04:25:39 +05:30
|
|
|
use prec, only: &
|
|
|
|
pInt
|
|
|
|
use results
|
|
|
|
use HDF5_utilities
|
|
|
|
use constitutive, only: &
|
|
|
|
constitutive_results
|
2019-04-06 10:01:02 +05:30
|
|
|
use crystallite, only: &
|
|
|
|
crystallite_results
|
2018-12-05 04:25:39 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: inc
|
2018-12-17 20:45:16 +05:30
|
|
|
real(pReal), intent(in) :: time
|
2018-12-05 04:25:39 +05:30
|
|
|
|
|
|
|
call results_openJobFile
|
2018-12-17 20:45:16 +05:30
|
|
|
call results_addIncrement(inc,time)
|
2019-04-06 10:01:02 +05:30
|
|
|
call constitutive_results
|
|
|
|
call crystallite_results
|
2019-01-07 01:26:36 +05:30
|
|
|
call results_removeLink('current') ! ToDo: put this into closeJobFile
|
2018-12-05 04:25:39 +05:30
|
|
|
call results_closeJobFile
|
|
|
|
|
|
|
|
end subroutine CPFEM_results
|
|
|
|
|
2016-01-17 20:33:54 +05:30
|
|
|
end module CPFEM2
|