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 , &
2016-01-17 20:33:54 +05:30
CPFEM_initAll
contains
!--------------------------------------------------------------------------------------------------
!> @brief call (thread safe) all module initializations
!--------------------------------------------------------------------------------------------------
subroutine CPFEM_initAll ( el , ip )
2016-01-20 21:49:05 +05:30
use prec , only : &
pInt
2016-01-17 20:33:54 +05:30
use prec , only : &
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-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
integer ( pInt ) , intent ( in ) :: el , & !< FE el number
ip !< FE integration point number
2016-01-20 21:49:05 +05:30
call DAMASK_interface_init ! Spectral and FEM interface to commandline
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
call mesh_init ( ip , el ) ! pass on coordinates to alter calcMode of first ip
call lattice_init
call material_init
2018-10-09 17:43:51 +05:30
call HDF5_utilities_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
2018-02-02 17:06:09 +05:30
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
2017-10-05 20:05:34 +05:30
use , intrinsic :: iso_fortran_env , only : &
compiler_version , &
compiler_options
#endif
2016-01-17 20:33:54 +05:30
use prec , only : &
2018-10-04 20:30:24 +05:30
pInt , pReal , pLongInt
2016-01-17 20:33:54 +05:30
use IO , only : &
IO_read_realFile , &
IO_read_intFile , &
IO_timeStamp , &
IO_error
use numerics , only : &
worldrank
use debug , only : &
debug_level , &
debug_CPFEM , &
debug_levelBasic , &
debug_levelExtensive
use FEsolving , only : &
restartRead , &
modelName
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 , &
crystallite_dPdF0 , &
crystallite_Tstar0_v
2018-10-04 20:30:24 +05:30
use hdf5
use HDF5_utilities , only : &
HDF5_openFile , &
HDF5_openGroup2 , &
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
integer ( pInt ) :: k , l , m , ph , homog
character ( len = 1024 ) :: rankStr
2018-10-09 14:27:06 +05:30
integer ( HID_T ) :: fileReadID , groupPlasticID , groupHomogID
2018-10-04 20:30:24 +05:30
integer :: hdferr
2016-01-17 20:33:54 +05:30
mainProcess : if ( worldrank == 0 ) then
write ( 6 , '(/,a)' ) ' <<<+- CPFEM init -+>>>'
write ( 6 , '(a15,a)' ) ' Current time: ' , IO_timeStamp ( )
#include "compilation_info.f90"
2018-02-16 20:06:18 +05:30
flush ( 6 )
2016-01-17 20:33:54 +05:30
endif mainProcess
2018-10-05 12:26:06 +05:30
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-10-04 20:30:24 +05:30
fileReadID = HDF5_openFile ( trim ( getSolverJobName ( ) ) / / trim ( rankStr ) / / '.hdf5' )
2018-10-05 12:26:06 +05:30
2018-10-09 14:27:06 +05:30
call HDF5_read ( material_phase , fileReadID , 'recordedPhase' )
!write(6,*) material_phase
2018-10-05 12:26:06 +05:30
call HDF5_read ( crystallite_F0 , fileReadID , 'convergedF' )
2018-10-09 14:27:06 +05:30
!write(6,*) crystallite_F0
call HDF5_read ( crystallite_Fp0 , fileReadID , 'convergedFp' )
call HDF5_read ( crystallite_Fi0 , fileReadID , 'convergedFi' )
call HDF5_read ( crystallite_Lp0 , fileReadID , 'convergedLp' )
call HDF5_read ( crystallite_Li0 , fileReadID , 'convergedLi' )
call HDF5_read ( crystallite_dPdF0 , fileReadID , 'convergeddPdF' )
call HDF5_read ( crystallite_Tstar0_v , fileReadID , 'convergedTstar' )
2018-10-04 20:30:24 +05:30
2018-10-09 14:27:06 +05:30
groupPlasticID = HDF5_openGroup2 ( fileReadID , 'PlasticPhases' )
write ( 6 , * ) groupPlasticID
do ph = 1_pInt , size ( phase_plasticity )
call HDF5_read ( plasticState ( ph ) % state0 , groupPlasticID , 'convergedStateConst' )
write ( 6 , * ) plasticState ( ph ) % state0
enddo
groupHomogID = HDF5_openGroup2 ( fileReadID , 'material_Nhomogenization' )
write ( 6 , * ) groupHomogID
do homog = 1_pInt , material_Nhomogenization
call HDF5_read ( homogState ( homog ) % state0 , groupHomogID , 'convergedStateHomog' )
write ( 6 , * ) homogState ( homog ) % state0
enddo
! call IO_read_intFile(777,'recordedPhase'//trim(rankStr),modelName,size(material_phase))
! read (777,rec=1) material_phase; close (777)
! call IO_read_realFile(777,'convergedF'//trim(rankStr),modelName,size(crystallite_F0))
! read (777,rec=1) crystallite_F0; close (777)
! call IO_read_realFile(777,'convergedFp'//trim(rankStr),modelName,size(crystallite_Fp0))
! read (777,rec=1) crystallite_Fp0; close (777)
! call IO_read_realFile(777,'convergedFi'//trim(rankStr),modelName,size(crystallite_Fi0))
! read (777,rec=1) crystallite_Fi0; close (777)
! call IO_read_realFile(777,'convergedLp'//trim(rankStr),modelName,size(crystallite_Lp0))
! read (777,rec=1) crystallite_Lp0; close (777)
! call IO_read_realFile(777,'convergedLi'//trim(rankStr),modelName,size(crystallite_Li0))
! read (777,rec=1) crystallite_Li0; close (777)
! call IO_read_realFile(777,'convergeddPdF'//trim(rankStr),modelName,size(crystallite_dPdF0))
! read (777,rec=1) crystallite_dPdF0; close (777)
! call IO_read_realFile(777,'convergedTstar'//trim(rankStr),modelName,size(crystallite_Tstar0_v))
! read (777,rec=1) crystallite_Tstar0_v; close (777)
! call IO_read_realFile(777,'convergedStateConst'//trim(rankStr),modelName)
! m = 0_pInt
! readPlasticityInstances: do ph = 1_pInt, size(phase_plasticity)
! do k = 1_pInt, plasticState(ph)%sizeState
! do l = 1, size(plasticState(ph)%state0(1,:))
! m = m+1_pInt
! read(777,rec=m) plasticState(ph)%state0(k,l)
! enddo; enddo
! enddo readPlasticityInstances
! close (777)
! call IO_read_realFile(777,'convergedStateHomog'//trim(rankStr),modelName)
! m = 0_pInt
! readHomogInstances: do homog = 1_pInt, material_Nhomogenization
! do k = 1_pInt, homogState(homog)%sizeState
! do l = 1, size(homogState(homog)%state0(1,:))
! m = m+1_pInt
! read(777,rec=m) homogState(homog)%state0(k,l)
! enddo; enddo
! enddo readHomogInstances
! close (777)
2016-01-17 20:33:54 +05:30
restartRead = . false .
endif
end subroutine CPFEM_init
!--------------------------------------------------------------------------------------------------
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 , &
vacancyfluxState , &
hydrogenfluxState , &
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 , &
crystallite_dPdF0 , &
crystallite_dPdF , &
crystallite_Tstar0_v , &
crystallite_Tstar_v
use IO , only : &
IO_write_jobRealFile , &
IO_warning
2018-09-20 23:12:58 +05:30
use HDF5_utilities , only : &
HDF5_createFile , &
HDF5_closeFile , &
HDF5_closeGroup , &
2018-09-25 20:12:43 +05:30
HDF5_addGroup2 , &
2018-10-09 14:27:06 +05:30
!HDF5_writeScalarDataset3, &
HDF5_write
2018-10-05 12:26:06 +05:30
!HDF5_addScalarDataset2
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
integer ( pInt ) :: i , k , l , m , ph , homog , mySource
2018-02-16 20:06:18 +05:30
character ( len = 32 ) :: rankStr
2018-10-04 20:30:24 +05:30
integer ( HID_T ) :: fileHandle , groupPlastic , groupHomog
2018-09-25 20:12:43 +05:30
integer :: hdferr
integer ( HSIZE_T ) :: hdfsize
2018-09-28 12:11:29 +05:30
real ( pReal ) , dimension ( 4 , 1 , 1 , 3 , 2 ) :: testData = reshape ( real ( [ 1 , 2 , 3 , 4 , 5 , 6 , 7 , 8 , 9 , 10 , 11 , 12 , 13 , 14 , 15 , &
16 , 17 , 18 , 19 , 20 , 21 , 22 , 23 , 24 ] , pReal ) , [ 4 , 1 , 1 , 3 , 2 ] )
2018-02-16 20:06:18 +05:30
if ( iand ( debug_level ( debug_CPFEM ) , debug_levelBasic ) / = 0_pInt ) &
write ( 6 , '(a)' ) '<< CPFEM >> aging states'
crystallite_F0 = crystallite_partionedF ! crystallite deformation (_subF is perturbed...)
crystallite_Fp0 = crystallite_Fp ! crystallite plastic deformation
crystallite_Lp0 = crystallite_Lp ! crystallite plastic velocity
crystallite_Fi0 = crystallite_Fi ! crystallite intermediate deformation
crystallite_Li0 = crystallite_Li ! crystallite intermediate velocity
crystallite_dPdF0 = crystallite_dPdF ! crystallite stiffness
crystallite_Tstar0_v = crystallite_Tstar_v ! crystallite 2nd Piola Kirchhoff stress
forall ( i = 1 : size ( plasticState ) ) plasticState ( i ) % state0 = plasticState ( i ) % state ! copy state in this lengthy way because: A component cannot be an array if the encompassing structure is an array
do i = 1 , size ( sourceState )
do mySource = 1 , phase_Nsources ( i )
sourceState ( i ) % p ( mySource ) % state0 = sourceState ( i ) % p ( mySource ) % state ! copy state in this lengthy way because: A component cannot be an array if the encompassing structure is an array
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
vacancyfluxState ( homog ) % state0 = vacancyfluxState ( homog ) % state
hydrogenfluxState ( homog ) % state0 = hydrogenfluxState ( homog ) % state
enddo
if ( restartWrite ) then
if ( iand ( debug_level ( debug_CPFEM ) , debug_levelBasic ) / = 0_pInt ) &
write ( 6 , '(a)' ) '<< CPFEM >> writing state variables of last converged step to binary files'
write ( rankStr , '(a1,i0)' ) '_' , worldrank
2018-09-28 12:11:29 +05:30
fileHandle = HDF5_createFile ( trim ( getSolverJobName ( ) ) / / trim ( rankStr ) / / '.hdf5' )
2018-09-25 20:12:43 +05:30
2018-10-09 14:27:06 +05:30
call HDF5_write ( material_phase , fileHandle , 'recordedPhase' )
call HDF5_write ( crystallite_F0 , fileHandle , 'convergedF' )
call HDF5_write ( crystallite_Fp0 , fileHandle , 'convergedFp' )
call HDF5_write ( crystallite_Fi0 , fileHandle , 'convergedFi' )
call HDF5_write ( crystallite_Lp0 , fileHandle , 'convergedLp' )
call HDF5_write ( crystallite_Li0 , fileHandle , 'convergedLi' )
call HDF5_write ( crystallite_dPdF0 , fileHandle , 'convergeddPdF' )
call HDF5_write ( crystallite_Tstar0_v , fileHandle , 'convergedTstar' )
2018-09-26 12:51:53 +05:30
2018-10-04 20:30:24 +05:30
groupPlastic = HDF5_addGroup2 ( fileHandle , 'PlasticPhases' )
do ph = 1_pInt , size ( phase_plasticity )
2018-10-09 14:27:06 +05:30
call HDF5_write ( plasticState ( ph ) % state0 , groupPlastic , 'convergedStateConst' )
2018-10-04 20:30:24 +05:30
enddo
groupHomog = HDF5_addGroup2 ( fileHandle , 'material_Nhomogenization' )
do homog = 1_pInt , material_Nhomogenization
2018-10-09 14:27:06 +05:30
call HDF5_write ( homogState ( homog ) % state0 , groupHomog , 'convergedStateHomog' )
2018-10-04 20:30:24 +05:30
enddo
2018-09-25 20:12:43 +05:30
2018-09-20 23:12:58 +05:30
call HDF5_closeFile ( fileHandle )
2018-10-09 14:27:06 +05:30
! call IO_write_jobRealFile(777,'recordedPhase'//trim(rankStr),size(material_phase))
! write (777,rec=1) material_phase; close (777)
! call IO_write_jobRealFile(777,'convergedF'//trim(rankStr),size(crystallite_F0))
! write (777,rec=1) crystallite_F0; close (777)
! call IO_write_jobRealFile(777,'convergedFp'//trim(rankStr),size(crystallite_Fp0))
! write (777,rec=1) crystallite_Fp0; close (777)
! call IO_write_jobRealFile(777,'convergedFi'//trim(rankStr),size(crystallite_Fi0))
! write (777,rec=1) crystallite_Fi0; close (777)
! call IO_write_jobRealFile(777,'convergedLp'//trim(rankStr),size(crystallite_Lp0))
! write (777,rec=1) crystallite_Lp0; close (777)
! call IO_write_jobRealFile(777,'convergedLi'//trim(rankStr),size(crystallite_Li0))
! write (777,rec=1) crystallite_Li0; close (777)
! call IO_write_jobRealFile(777,'convergeddPdF'//trim(rankStr),size(crystallite_dPdF0))
! write (777,rec=1) crystallite_dPdF0; close (777)
! call IO_write_jobRealFile(777,'convergedTstar'//trim(rankStr),size(crystallite_Tstar0_v))
! write (777,rec=1) crystallite_Tstar0_v; close (777)
! call IO_write_jobRealFile(777,'convergedStateConst'//trim(rankStr))
! m = 0_pInt
! writePlasticityInstances: do ph = 1_pInt, size(phase_plasticity)
! do k = 1_pInt, plasticState(ph)%sizeState
! do l = 1, size(plasticState(ph)%state0(1,:))
! m = m+1_pInt
! write(777,rec=m) plasticState(ph)%state0(k,l)
! enddo; enddo
! enddo writePlasticityInstances
! close (777)
! call IO_write_jobRealFile(777,'convergedStateHomog'//trim(rankStr))
! m = 0_pInt
! writeHomogInstances: do homog = 1_pInt, material_Nhomogenization
! do k = 1_pInt, homogState(homog)%sizeState
! do l = 1, size(homogState(homog)%state0(1,:))
! m = m+1_pInt
! write(777,rec=m) homogState(homog)%state0(k,l)
! enddo; enddo
! enddo writeHomogInstances
! close (777)
2018-02-16 20:06:18 +05:30
endif
if ( iand ( debug_level ( debug_CPFEM ) , debug_levelBasic ) / = 0_pInt ) &
write ( 6 , '(a)' ) '<< CPFEM >> done aging states'
end subroutine CPFEM_age
2016-01-17 20:33:54 +05:30
end module CPFEM2