2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
! $Id$
!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @author Christoph Kords, Max-Planck-Institut für Eisenforschung GmbH
!> @brief crystallite state integration functions and reporting of results
!--------------------------------------------------------------------------------------------------
2010-10-01 17:48:49 +05:30
2012-08-31 01:56:28 +05:30
module crystallite
2013-04-29 16:47:30 +05:30
use prec , only : &
pReal , &
pInt
2012-08-31 01:56:28 +05:30
implicit none
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
private
2013-12-12 22:39:59 +05:30
character ( len = 64 ) , dimension ( : , : ) , allocatable , private :: &
2013-02-22 04:38:36 +05:30
crystallite_output !< name of each post result output
2013-12-12 22:39:59 +05:30
integer ( pInt ) , public , protected :: &
2013-05-17 23:22:46 +05:30
crystallite_maxSizePostResults !< description not available
2013-12-12 22:39:59 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , public , protected :: &
2013-05-17 23:22:46 +05:30
crystallite_sizePostResults !< description not available
2013-12-12 22:39:59 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , private :: &
2013-05-17 23:22:46 +05:30
crystallite_sizePostResult !< description not available
2014-08-26 20:14:32 +05:30
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable , public :: &
2013-10-16 18:34:59 +05:30
crystallite_dt !< requested time increment of each grain
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable , private :: &
2013-02-22 04:38:36 +05:30
crystallite_subdt , & !< substepped time increment of each grain
crystallite_subFrac , & !< already calculated fraction of increment
2013-10-16 18:34:59 +05:30
crystallite_subStep !< size of next integration step
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable , public :: &
2013-02-22 04:38:36 +05:30
crystallite_Tstar_v , & !< current 2nd Piola-Kirchhoff stress vector (end of converged time step)
crystallite_Tstar0_v , & !< 2nd Piola-Kirchhoff stress vector at start of FE inc
crystallite_partionedTstar0_v !< 2nd Piola-Kirchhoff stress vector at start of homog inc
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable , private :: &
2013-02-22 04:38:36 +05:30
crystallite_subTstar0_v , & !< 2nd Piola-Kirchhoff stress vector at start of crystallite inc
crystallite_orientation , & !< orientation as quaternion
crystallite_orientation0 , & !< initial orientation as quaternion
2014-08-26 20:14:32 +05:30
crystallite_rotation !< grain rotation away from initial orientation as axis-angle (in degrees) in crystal reference frame
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : , : , : ) , allocatable , public :: &
2013-02-22 04:38:36 +05:30
crystallite_Fp , & !< current plastic def grad (end of converged time step)
crystallite_Fp0 , & !< plastic def grad at start of FE inc
crystallite_partionedFp0 , & !< plastic def grad at start of homog inc
crystallite_F0 , & !< def grad at start of FE inc
crystallite_partionedF , & !< def grad to be reached at end of homog inc
crystallite_partionedF0 , & !< def grad at start of homog inc
crystallite_Lp , & !< current plastic velocitiy grad (end of converged time step)
crystallite_Lp0 , & !< plastic velocitiy grad at start of FE inc
crystallite_partionedLp0 , & !< plastic velocity grad at start of homog inc
crystallite_P !< 1st Piola-Kirchhoff stress per grain
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : , : , : ) , allocatable , private :: &
2014-09-03 01:16:52 +05:30
crystallite_Fe , & !< current "elastic" def grad (end of converged time step)
2013-02-22 04:38:36 +05:30
crystallite_subFe0 , & !< "elastic" def grad at start of crystallite inc
crystallite_invFp , & !< inverse of current plastic def grad (end of converged time step)
crystallite_subFp0 , & !< plastic def grad at start of crystallite inc
crystallite_subF , & !< def grad to be reached at end of crystallite inc
crystallite_subF0 , & !< def grad at start of crystallite inc
crystallite_subLp0 , & !< plastic velocity grad at start of crystallite inc
crystallite_disorientation !< disorientation between two neighboring ips (only calculated for single grain IPs)
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : , : ) , allocatable , public :: &
2013-02-22 04:38:36 +05:30
crystallite_dPdF , & !< current individual dPdF per grain (end of converged time step)
crystallite_dPdF0 , & !< individual dPdF per grain at start of FE inc
crystallite_partioneddPdF0 !< individual dPdF per grain at start of homog inc
2013-12-12 22:39:59 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : , : ) , allocatable , private :: &
2013-02-22 04:38:36 +05:30
crystallite_fallbackdPdF !< dPdF fallback for non-converged grains (elastic prediction)
2013-12-12 22:39:59 +05:30
logical , dimension ( : , : , : ) , allocatable , public :: &
2013-02-22 04:38:36 +05:30
crystallite_requested !< flag to request crystallite calculation
2013-12-12 22:39:59 +05:30
logical , dimension ( : , : , : ) , allocatable , public , protected :: &
2013-03-01 17:18:29 +05:30
crystallite_converged , & !< convergence flag
crystallite_localPlasticity !< indicates this grain to have purely local constitutive law
2013-12-12 22:39:59 +05:30
logical , dimension ( : , : , : ) , allocatable , private :: &
2013-02-22 04:38:36 +05:30
crystallite_todo !< flag to indicate need for further computation
2013-12-12 22:39:59 +05:30
logical , dimension ( : , : ) , allocatable , private :: &
2013-05-17 23:22:46 +05:30
crystallite_clearToWindForward , & !< description not available
crystallite_clearToCutback , & !< description not available
crystallite_syncSubFrac , & !< description not available
crystallite_syncSubFracCompleted , & !< description not available
crystallite_neighborEnforcedCutback !< description not available
2013-02-22 04:38:36 +05:30
2014-08-26 20:14:32 +05:30
enum , bind ( c )
2013-12-12 22:39:59 +05:30
enumerator :: undefined_ID , &
phase_ID , &
texture_ID , &
volume_ID , &
grainrotationx_ID , &
grainrotationy_ID , &
grainrotationz_ID , &
orientation_ID , &
grainrotation_ID , &
eulerangles_ID , &
defgrad_ID , &
fe_ID , &
fp_ID , &
lp_ID , &
e_ID , &
ee_ID , &
p_ID , &
s_ID , &
elasmatrix_ID , &
neighboringip_ID , &
neighboringelement_ID
end enum
2014-08-26 20:14:32 +05:30
integer ( kind ( undefined_ID ) ) , dimension ( : , : ) , allocatable , private :: &
2013-12-12 22:39:59 +05:30
crystallite_outputID !< ID of each post result output
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
public :: &
crystallite_init , &
crystallite_stressAndItsTangent , &
crystallite_orientations , &
2014-09-10 14:07:12 +05:30
crystallite_push33ToRef , &
2013-02-22 04:38:36 +05:30
crystallite_postResults
private :: &
2014-08-26 20:14:32 +05:30
crystallite_integrateStateFPI , &
2013-02-22 04:38:36 +05:30
crystallite_integrateStateEuler , &
crystallite_integrateStateAdaptiveEuler , &
crystallite_integrateStateRK4 , &
crystallite_integrateStateRKCK45 , &
crystallite_integrateStress , &
crystallite_stateJump
2014-08-26 20:14:32 +05:30
2012-08-31 01:56:28 +05:30
contains
2009-05-07 21:57:36 +05:30
2011-03-29 12:57:19 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief allocates and initialize per grain variables
!--------------------------------------------------------------------------------------------------
2014-10-10 17:58:57 +05:30
subroutine crystallite_init
2013-02-22 04:38:36 +05:30
use , intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
2013-04-29 16:47:30 +05:30
use debug , only : &
debug_info , &
debug_reset , &
debug_level , &
debug_crystallite , &
debug_levelBasic
2013-04-16 22:37:27 +05:30
use numerics , only : &
2014-10-10 01:53:06 +05:30
worldrank , &
2014-08-26 20:14:32 +05:30
usePingPong
2013-05-17 23:22:46 +05:30
use math , only : &
2013-04-29 16:47:30 +05:30
math_I3 , &
math_EulerToR , &
math_inv33 , &
math_transpose33 , &
math_mul33xx33 , &
math_mul33x33
use FEsolving , only : &
FEsolving_execElem , &
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems , &
mesh_maxNips , &
mesh_maxNipNeighbors
use IO , only : &
2013-06-27 00:49:00 +05:30
IO_read , &
2013-04-29 16:47:30 +05:30
IO_timeStamp , &
IO_open_jobFile_stat , &
IO_open_file , &
IO_lc , &
IO_getTag , &
IO_isBlank , &
IO_stringPos , &
IO_stringValue , &
IO_write_jobFile , &
2013-12-12 22:39:59 +05:30
IO_error , &
IO_EOF
2012-08-31 01:56:28 +05:30
use material
2013-04-29 16:47:30 +05:30
use lattice , only : &
2014-03-09 02:20:31 +05:30
lattice_structure
2013-04-29 16:47:30 +05:30
use constitutive , only : &
2014-09-03 01:16:52 +05:30
constitutive_microstructure ! derived (shortcut) quantities of given state
2014-08-26 20:14:32 +05:30
2012-08-31 01:56:28 +05:30
implicit none
2013-10-16 18:34:59 +05:30
integer ( pInt ) , parameter :: &
2013-12-12 22:39:59 +05:30
FILEUNIT = 200_pInt , &
2013-10-16 18:34:59 +05:30
MAXNCHUNKS = 2_pInt
2014-08-26 20:14:32 +05:30
2013-10-16 18:34:59 +05:30
integer ( pInt ) , dimension ( 1 + 2 * MAXNCHUNKS ) :: positions
2013-04-29 16:47:30 +05:30
integer ( pInt ) :: &
g , & !< grain number
i , & !< integration point number
e , & !< element number
gMax , & !< maximum number of grains
iMax , & !< maximum number of integration points
eMax , & !< maximum number of elements
nMax , & !< maximum number of ip neighbors
myNgrains , & !< number of grains in current IP
2013-12-12 22:39:59 +05:30
section = 0_pInt , &
2013-04-29 16:47:30 +05:30
j , &
p , &
2013-12-13 19:44:17 +05:30
output = 0_pInt , &
2014-03-09 02:20:31 +05:30
mySize
2013-10-19 00:27:28 +05:30
character ( len = 65536 ) :: &
2013-12-12 22:39:59 +05:30
tag = '' , &
line = ''
2014-08-26 20:14:32 +05:30
2014-10-10 21:51:10 +05:30
mainProcess : if ( worldrank == 0 ) then
write ( 6 , '(/,a)' ) ' <<<+- crystallite init -+>>>'
write ( 6 , '(a)' ) ' $Id$'
write ( 6 , '(a15,a)' ) ' Current time: ' , IO_timeStamp ( )
2012-02-01 00:48:55 +05:30
#include "compilation_info.f90"
2014-10-10 21:51:10 +05:30
endif mainProcess
2014-08-26 20:14:32 +05:30
2012-08-31 01:56:28 +05:30
gMax = homogenization_maxNgrains
iMax = mesh_maxNips
eMax = mesh_NcpElems
nMax = mesh_maxNipNeighbors
2014-05-27 20:16:03 +05:30
2014-08-26 20:14:32 +05:30
2013-12-12 22:39:59 +05:30
allocate ( crystallite_Tstar0_v ( 6 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_partionedTstar0_v ( 6 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subTstar0_v ( 6 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_Tstar_v ( 6 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_P ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_F0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_partionedF0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_partionedF ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subF0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subF ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_Fp0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_partionedFp0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subFp0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_Fp ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_invFp ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_Fe ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subFe0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_Lp0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_partionedLp0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subLp0 ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_Lp ( 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_dPdF ( 3 , 3 , 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_dPdF0 ( 3 , 3 , 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_partioneddPdF0 ( 3 , 3 , 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_fallbackdPdF ( 3 , 3 , 3 , 3 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_dt ( gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subdt ( gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subFrac ( gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_subStep ( gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_orientation ( 4 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_orientation0 ( 4 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_rotation ( 4 , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_disorientation ( 4 , nMax , gMax , iMax , eMax ) , source = 0.0_pReal )
allocate ( crystallite_localPlasticity ( gMax , iMax , eMax ) , source = . true . )
allocate ( crystallite_requested ( gMax , iMax , eMax ) , source = . false . )
allocate ( crystallite_todo ( gMax , iMax , eMax ) , source = . false . )
allocate ( crystallite_converged ( gMax , iMax , eMax ) , source = . true . )
allocate ( crystallite_clearToWindForward ( iMax , eMax ) , source = . true . )
allocate ( crystallite_syncSubFrac ( iMax , eMax ) , source = . false . )
allocate ( crystallite_syncSubFracCompleted ( iMax , eMax ) , source = . false . )
allocate ( crystallite_clearToCutback ( iMax , eMax ) , source = . true . )
allocate ( crystallite_neighborEnforcedCutback ( iMax , eMax ) , source = . false . )
2012-08-31 01:56:28 +05:30
allocate ( crystallite_output ( maxval ( crystallite_Noutput ) , &
2013-12-12 22:39:59 +05:30
material_Ncrystallite ) ) ; crystallite_output = ''
allocate ( crystallite_outputID ( maxval ( crystallite_Noutput ) , &
material_Ncrystallite ) , source = undefined_ID )
allocate ( crystallite_sizePostResults ( material_Ncrystallite ) , source = 0_pInt )
2012-08-31 01:56:28 +05:30
allocate ( crystallite_sizePostResult ( maxval ( crystallite_Noutput ) , &
2013-12-12 22:39:59 +05:30
material_Ncrystallite ) , source = 0_pInt )
2014-08-26 20:14:32 +05:30
2013-12-12 22:39:59 +05:30
if ( . not . IO_open_jobFile_stat ( FILEUNIT , material_localFileExt ) ) & ! no local material configuration present...
call IO_open_file ( FILEUNIT , material_configFile ) ! ...open material.config file
rewind ( FILEUNIT )
do while ( trim ( line ) / = IO_EOF . and . IO_lc ( IO_getTag ( line , '<' , '>' ) ) / = material_partCrystallite ) ! wind forward to <crystallite>
line = IO_read ( FILEUNIT )
2012-08-31 01:56:28 +05:30
enddo
2014-08-26 20:14:32 +05:30
2013-12-12 22:39:59 +05:30
do while ( trim ( line ) / = IO_EOF ) ! read through sections of crystallite part
line = IO_read ( FILEUNIT )
2013-02-22 04:38:36 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
2013-12-12 22:39:59 +05:30
if ( IO_getTag ( line , '<' , '>' ) / = '' ) then ! stop at next part
line = IO_read ( FILEUNIT , . true . ) ! reset IO_read
2014-08-26 20:14:32 +05:30
exit
2013-12-12 22:39:59 +05:30
endif
2013-02-22 04:38:36 +05:30
if ( IO_getTag ( line , '[' , ']' ) / = '' ) then ! next section
2012-08-31 01:56:28 +05:30
section = section + 1_pInt
2013-02-22 04:38:36 +05:30
output = 0_pInt ! reset output counter
2013-12-20 16:43:12 +05:30
cycle ! skip to next line
2012-08-31 01:56:28 +05:30
endif
if ( section > 0_pInt ) then
positions = IO_stringPos ( line , maxNchunks )
2013-02-22 04:38:36 +05:30
tag = IO_lc ( IO_stringValue ( line , positions , 1_pInt ) ) ! extract key
2012-08-31 01:56:28 +05:30
select case ( tag )
case ( '(output)' )
output = output + 1_pInt
crystallite_output ( output , section ) = IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2013-12-13 19:44:17 +05:30
select case ( crystallite_output ( output , section ) )
2013-12-12 22:39:59 +05:30
case ( 'phase' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = phase_ID
2013-12-12 22:39:59 +05:30
case ( 'texture' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = texture_ID
2013-12-12 22:39:59 +05:30
case ( 'volume' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = volume_ID
2013-12-12 22:39:59 +05:30
case ( 'grainrotationx' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = grainrotationx_ID
2013-12-12 22:39:59 +05:30
case ( 'grainrotationy' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = grainrotationy_ID
2013-12-12 22:39:59 +05:30
case ( 'grainrotationz' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = grainrotationx_ID
2013-12-12 22:39:59 +05:30
case ( 'orientation' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = orientation_ID
2013-12-12 22:39:59 +05:30
case ( 'grainrotation' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = grainrotation_ID
2013-12-12 22:39:59 +05:30
case ( 'eulerangles' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = eulerangles_ID
2013-12-12 22:39:59 +05:30
case ( 'defgrad' , 'f' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = defgrad_ID
2013-12-12 22:39:59 +05:30
case ( 'fe' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = fe_ID
2013-12-12 22:39:59 +05:30
case ( 'fp' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = fp_ID
2013-12-20 16:43:12 +05:30
case ( 'lp' )
crystallite_outputID ( output , section ) = lp_ID
2013-12-12 22:39:59 +05:30
case ( 'e' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = e_ID
2013-12-12 22:39:59 +05:30
case ( 'ee' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = ee_ID
2013-12-12 22:39:59 +05:30
case ( 'p' , 'firstpiola' , '1piola' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = p_ID
2013-12-12 22:39:59 +05:30
case ( 's' , 'tstar' , 'secondpiola' , '2ndpiola' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = s_ID
2013-12-12 22:39:59 +05:30
case ( 'elasmatrix' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = elasmatrix_ID
2013-12-12 22:39:59 +05:30
case ( 'neighboringip' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = neighboringip_ID
2013-12-12 22:39:59 +05:30
case ( 'neighboringelement' )
2013-12-13 18:49:17 +05:30
crystallite_outputID ( output , section ) = neighboringelement_ID
2013-12-12 22:39:59 +05:30
case default
call IO_error ( 105_pInt , ext_msg = IO_stringValue ( line , positions , 2_pInt ) / / ' (Crystallite)' )
end select
2012-08-31 01:56:28 +05:30
end select
endif
enddo
2014-08-26 20:14:32 +05:30
2013-12-12 22:39:59 +05:30
close ( FILEUNIT )
2014-08-26 20:14:32 +05:30
2012-08-31 01:56:28 +05:30
do i = 1_pInt , material_Ncrystallite
do j = 1_pInt , crystallite_Noutput ( i )
2013-12-12 22:39:59 +05:30
select case ( crystallite_outputID ( j , i ) )
2014-10-10 17:58:57 +05:30
case ( phase_ID , texture_ID , volume_ID , grainrotationx_ID , grainrotationy_ID , grainrotationz_ID )
2012-08-31 01:56:28 +05:30
mySize = 1_pInt
2013-12-12 22:39:59 +05:30
case ( orientation_ID , grainrotation_ID ) ! orientation as quaternion, or deviation from initial grain orientation in axis-angle form (angle in degrees)
2012-08-31 01:56:28 +05:30
mySize = 4_pInt
2013-12-12 22:39:59 +05:30
case ( eulerangles_ID )
2012-08-31 01:56:28 +05:30
mySize = 3_pInt
2013-12-12 22:39:59 +05:30
case ( defgrad_ID , fe_ID , fp_ID , lp_ID , e_ID , ee_ID , p_ID , s_ID )
2012-08-31 01:56:28 +05:30
mySize = 9_pInt
2013-12-12 22:39:59 +05:30
case ( elasmatrix_ID )
2014-08-26 20:14:32 +05:30
mySize = 36_pInt
2013-12-12 22:39:59 +05:30
case ( neighboringip_ID , neighboringelement_ID )
2013-05-08 17:32:30 +05:30
mySize = mesh_maxNipNeighbors
2012-08-31 01:56:28 +05:30
case default
2014-08-26 20:14:32 +05:30
mySize = 0_pInt
2012-08-31 01:56:28 +05:30
end select
2014-08-26 20:14:32 +05:30
2013-10-19 00:27:28 +05:30
outputFound : if ( mySize > 0_pInt ) then
2012-08-31 01:56:28 +05:30
crystallite_sizePostResult ( j , i ) = mySize
crystallite_sizePostResults ( i ) = crystallite_sizePostResults ( i ) + mySize
2013-10-19 00:27:28 +05:30
endif outputFound
2012-08-31 01:56:28 +05:30
enddo
enddo
2014-08-26 20:14:32 +05:30
2012-08-31 01:56:28 +05:30
crystallite_maxSizePostResults = 0_pInt
do j = 1_pInt , material_Nmicrostructure
if ( microstructure_active ( j ) ) &
crystallite_maxSizePostResults = max ( crystallite_maxSizePostResults , &
crystallite_sizePostResults ( microstructure_crystallite ( j ) ) )
enddo
2009-06-16 14:33:30 +05:30
2013-04-29 16:47:30 +05:30
!--------------------------------------------------------------------------------------------------
2010-02-25 23:09:11 +05:30
! write description file for crystallite output
2013-12-12 22:39:59 +05:30
call IO_write_jobFile ( FILEUNIT , 'outputCrystallite' )
2014-08-26 20:14:32 +05:30
2012-08-31 01:56:28 +05:30
do p = 1_pInt , material_Ncrystallite
2013-12-12 22:39:59 +05:30
write ( FILEUNIT , '(/,a,/)' ) '[' / / trim ( crystallite_name ( p ) ) / / ']'
2012-08-31 01:56:28 +05:30
do e = 1_pInt , crystallite_Noutput ( p )
2013-12-12 22:39:59 +05:30
write ( FILEUNIT , '(a,i4)' ) trim ( crystallite_output ( e , p ) ) / / char ( 9 ) , crystallite_sizePostResult ( e , p )
2012-08-31 01:56:28 +05:30
enddo
enddo
2014-08-26 20:14:32 +05:30
2013-12-12 22:39:59 +05:30
close ( FILEUNIT )
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
!--------------------------------------------------------------------------------------------------
! initialize
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 ) ! iterate over all cp elements
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) ) ! look up homogenization-->grainCount
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1_pInt : myNgrains )
crystallite_Fp0 ( 1 : 3 , 1 : 3 , g , i , e ) = math_EulerToR ( material_EulerAngles ( 1 : 3 , g , i , e ) ) ! plastic def gradient reflects init orientation
crystallite_F0 ( 1 : 3 , 1 : 3 , g , i , e ) = math_I3
crystallite_localPlasticity ( g , i , e ) = phase_localPlasticity ( material_phase ( g , i , e ) )
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) = math_transpose33 ( crystallite_Fp0 ( 1 : 3 , 1 : 3 , g , i , e ) )
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_Fp0 ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_requested ( g , i , e ) = . true .
endforall
enddo
!$OMP END PARALLEL DO
2014-08-26 20:14:32 +05:30
2013-05-17 23:22:46 +05:30
if ( any ( . not . crystallite_localPlasticity ) . and . . not . usePingPong ) call IO_error ( 601_pInt ) ! exit if nonlocal but no ping-pong
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
crystallite_partionedFp0 = crystallite_Fp0
crystallite_partionedF0 = crystallite_F0
crystallite_partionedF = crystallite_F0
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
call crystallite_orientations ( )
crystallite_orientation0 = crystallite_orientation ! store initial orientations for calculation of grain rotations
2009-12-22 17:58:02 +05:30
2010-11-03 22:52:48 +05:30
2013-04-29 16:47:30 +05:30
!$OMP PARALLEL DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
do g = 1_pInt , myNgrains
2014-10-10 17:58:57 +05:30
call constitutive_microstructure ( &
2014-09-23 16:08:20 +05:30
crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-09-03 01:16:52 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! update dependent state variables to be consistent with basic states
2014-06-25 04:51:25 +05:30
enddo
2013-04-29 16:47:30 +05:30
enddo
enddo
!$OMP END PARALLEL DO
2014-06-17 00:49:38 +05:30
2014-08-08 02:38:34 +05:30
call crystallite_stressAndItsTangent ( . true . ) ! request elastic answers
2013-04-29 16:47:30 +05:30
crystallite_fallbackdPdF = crystallite_dPdF ! use initial elastic stiffness as fallback
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
!--------------------------------------------------------------------------------------------------
! debug output
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_Fe: ' , shape ( crystallite_Fe )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_Fp: ' , shape ( crystallite_Fp )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_Lp: ' , shape ( crystallite_Lp )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_F0: ' , shape ( crystallite_F0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_Fp0: ' , shape ( crystallite_Fp0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_Lp0: ' , shape ( crystallite_Lp0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_partionedF: ' , shape ( crystallite_partionedF )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_partionedF0: ' , shape ( crystallite_partionedF0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_partionedFp0: ' , shape ( crystallite_partionedFp0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_partionedLp0: ' , shape ( crystallite_partionedLp0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subF: ' , shape ( crystallite_subF )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subF0: ' , shape ( crystallite_subF0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subFe0: ' , shape ( crystallite_subFe0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subFp0: ' , shape ( crystallite_subFp0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subLp0: ' , shape ( crystallite_subLp0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_P: ' , shape ( crystallite_P )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_Tstar_v: ' , shape ( crystallite_Tstar_v )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_Tstar0_v: ' , shape ( crystallite_Tstar0_v )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_partionedTstar0_v: ' , shape ( crystallite_partionedTstar0_v )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subTstar0_v: ' , shape ( crystallite_subTstar0_v )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_dPdF: ' , shape ( crystallite_dPdF )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_dPdF0: ' , shape ( crystallite_dPdF0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_partioneddPdF0: ' , shape ( crystallite_partioneddPdF0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_fallbackdPdF: ' , shape ( crystallite_fallbackdPdF )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_orientation: ' , shape ( crystallite_orientation )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_orientation0: ' , shape ( crystallite_orientation0 )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_rotation: ' , shape ( crystallite_rotation )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_disorientation: ' , shape ( crystallite_disorientation )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_dt: ' , shape ( crystallite_dt )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subdt: ' , shape ( crystallite_subdt )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subFrac: ' , shape ( crystallite_subFrac )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_subStep: ' , shape ( crystallite_subStep )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_localPlasticity: ' , shape ( crystallite_localPlasticity )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_requested: ' , shape ( crystallite_requested )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_todo: ' , shape ( crystallite_todo )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_converged: ' , shape ( crystallite_converged )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_sizePostResults: ' , shape ( crystallite_sizePostResults )
write ( 6 , '(a35,1x,7(i8,1x))' ) 'crystallite_sizePostResult: ' , shape ( crystallite_sizePostResult )
2013-05-17 23:22:46 +05:30
write ( 6 , '(/,a35,1x,i10)' ) 'Number of nonlocal grains: ' , count ( . not . crystallite_localPlasticity )
2013-04-29 16:47:30 +05:30
flush ( 6 )
endif
2010-11-03 22:52:48 +05:30
2012-08-31 01:56:28 +05:30
call debug_info
call debug_reset
2010-11-03 22:52:48 +05:30
2012-03-09 01:55:28 +05:30
end subroutine crystallite_init
2009-05-07 21:57:36 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculate stress (P) and tangent (dPdF) for crystallites
!--------------------------------------------------------------------------------------------------
2014-08-08 02:38:34 +05:30
subroutine crystallite_stressAndItsTangent ( updateJaco )
2013-04-29 16:47:30 +05:30
use numerics , only : &
subStepMinCryst , &
subStepSizeCryst , &
stepIncreaseCryst , &
pert_Fg , &
pert_method , &
nCryst , &
numerics_integrator , &
numerics_integrationMode , &
numerics_timeSyncing , &
relevantStrain , &
analyticJaco
use debug , only : &
debug_level , &
debug_crystallite , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_e , &
debug_i , &
debug_g , &
debug_CrystalliteLoopDistribution
use IO , only : &
2014-08-08 02:46:37 +05:30
IO_warning , &
IO_error
2013-04-29 16:47:30 +05:30
use math , only : &
math_inv33 , &
math_identity2nd , &
math_transpose33 , &
math_mul33x33 , &
math_mul66x6 , &
math_Mandel6to33 , &
math_Mandel33to6 , &
math_I3 , &
2013-10-19 00:27:28 +05:30
math_mul3333xx3333 , &
2014-08-08 02:38:34 +05:30
math_mul33xx33 , &
math_invert
2013-04-29 16:47:30 +05:30
use FEsolving , only : &
2014-08-26 20:14:32 +05:30
FEsolving_execElem , &
2013-04-29 16:47:30 +05:30
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems , &
mesh_maxNips , &
mesh_ipNeighborhood , &
FE_NipNeighbors , &
FE_geomtype , &
FE_cellType
use material , only : &
homogenization_Ngrains , &
2014-05-12 18:30:37 +05:30
plasticState , &
2014-06-25 04:51:25 +05:30
damageState , &
thermalState , &
2014-06-23 00:28:29 +05:30
mappingConstitutive , &
2013-04-29 16:47:30 +05:30
homogenization_maxNgrains
use constitutive , only : &
2014-08-08 02:38:34 +05:30
constitutive_TandItsTangent , &
constitutive_LpAndItsTangent
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
implicit none
2013-05-17 23:22:46 +05:30
logical , intent ( in ) :: &
2014-08-08 02:38:34 +05:30
updateJaco !< whether to update the Jacobian (stiffness) or not
2013-05-17 23:22:46 +05:30
real ( pReal ) :: &
myPert , & ! perturbation with correct sign
formerSubStep , &
subFracIntermediate
real ( pReal ) , dimension ( 3 , 3 ) :: &
invFp , & ! inverse of the plastic deformation gradient
Fe_guess , & ! guess for elastic deformation gradient
Tstar ! 2nd Piola-Kirchhoff stress tensor
2013-04-29 16:47:30 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
2013-05-17 23:22:46 +05:30
dPdF_perturbation1 , &
dPdF_perturbation2
2013-04-29 16:47:30 +05:30
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
2013-05-17 23:22:46 +05:30
F_backup , &
Fp_backup , &
InvFp_backup , &
Fe_backup , &
Lp_backup , &
P_backup
2013-04-29 16:47:30 +05:30
real ( pReal ) , dimension ( 6 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
2013-05-17 23:22:46 +05:30
Tstar_v_backup
integer ( pInt ) :: &
NiterationCrystallite , & ! number of iterations in crystallite loop
e , & ! element index
i , & ! integration point index
g , & ! grain index
k , &
l , &
n , startIP , endIP , &
neighboring_e , &
neighboring_i , &
o , &
p , &
perturbation , & ! loop counter for forward,backward perturbation mode
myNgrains
2013-04-29 16:47:30 +05:30
logical , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
convergenceFlag_backup
! local variables used for calculating analytic Jacobian
2014-08-08 19:24:08 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: junk
2013-04-29 16:47:30 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: dSdFe , &
dFedF , &
dSdF , &
2014-08-08 02:38:34 +05:30
junk2 , &
dLpdS , dFpinvdF , rhs_3333 , lhs_3333 , temp_3333
real ( pReal ) , dimension ( 9 , 9 ) :: temp_99
logical :: error
2014-08-26 20:14:32 +05:30
2014-05-19 22:13:32 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt &
. and . FEsolving_execElem ( 1 ) < = debug_e &
. and . debug_e < = FEsolving_execElem ( 2 ) ) then
2014-08-27 21:24:11 +05:30
write ( 6 , '(/,a,i8,1x,a,i8,a,1x,i2,1x,i3)' ) '<< CRYST >> values at el (elFE) ip g ' , &
debug_e , '(' , mesh_element ( 1 , debug_e ) , ')' , debug_i , debug_g
2014-05-27 20:16:03 +05:30
write ( 6 , '(a,/,3(12x,3(f14.9,1x)/))' ) '<< CRYST >> F0 ' , &
math_transpose33 ( crystallite_partionedF0 ( 1 : 3 , 1 : 3 , debug_g , debug_i , debug_e ) )
write ( 6 , '(a,/,3(12x,3(f14.9,1x)/))' ) '<< CRYST >> Fp0' , &
math_transpose33 ( crystallite_partionedFp0 ( 1 : 3 , 1 : 3 , debug_g , debug_i , debug_e ) )
write ( 6 , '(a,/,3(12x,3(f14.9,1x)/))' ) '<< CRYST >> Lp0' , &
math_transpose33 ( crystallite_partionedLp0 ( 1 : 3 , 1 : 3 , debug_g , debug_i , debug_e ) )
write ( 6 , '(a,/,3(12x,3(f14.9,1x)/))' ) '<< CRYST >> F ' , &
math_transpose33 ( crystallite_partionedF ( 1 : 3 , 1 : 3 , debug_g , debug_i , debug_e ) )
2013-04-29 16:47:30 +05:30
endif
!--------------------------------------------------------------------------------------------------
! initialize to starting condition
crystallite_subStep = 0.0_pReal
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL DO PRIVATE(myNgrains)
elementLooping1 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , &
g = 1_pInt : myNgrains , crystallite_requested ( g , i , e ) )
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % partionedState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % partionedState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % partionedState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
2014-05-27 20:16:03 +05:30
crystallite_subFp0 ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_partionedFp0 ( 1 : 3 , 1 : 3 , g , i , e ) ! ...plastic def grad
crystallite_subLp0 ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_partionedLp0 ( 1 : 3 , 1 : 3 , g , i , e ) ! ...plastic velocity grad
crystallite_dPdF0 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) = crystallite_partioneddPdF0 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) ! ...stiffness
crystallite_subF0 ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_partionedF0 ( 1 : 3 , 1 : 3 , g , i , e ) ! ...def grad
crystallite_subTstar0_v ( 1 : 6 , g , i , e ) = crystallite_partionedTstar0_v ( 1 : 6 , g , i , e ) !...2nd PK stress
crystallite_subFe0 ( 1 : 3 , 1 : 3 , g , i , e ) = math_mul33x33 ( crystallite_subF0 ( 1 : 3 , 1 : 3 , g , i , e ) , &
math_inv33 ( crystallite_subFp0 ( 1 : 3 , 1 : 3 , g , i , e ) ) ) ! only needed later on for stiffness calculation
crystallite_subFrac ( g , i , e ) = 0.0_pReal
crystallite_subStep ( g , i , e ) = 1.0_pReal / subStepSizeCryst
crystallite_todo ( g , i , e ) = . true .
crystallite_converged ( g , i , e ) = . false . ! pretend failed step of twice the required size
endforall
enddo elementLooping1
!$OMP END PARALLEL DO
singleRun : if ( FEsolving_execELem ( 1 ) == FEsolving_execElem ( 2 ) . and . &
2013-05-17 23:22:46 +05:30
FEsolving_execIP ( 1 , FEsolving_execELem ( 1 ) ) == FEsolving_execIP ( 2 , FEsolving_execELem ( 1 ) ) ) then
startIP = FEsolving_execIP ( 1 , FEsolving_execELem ( 1 ) )
endIP = startIP
2014-05-27 20:16:03 +05:30
else singleRun
2013-05-17 23:22:46 +05:30
startIP = 1_pInt
endIP = mesh_maxNips
2014-05-27 20:16:03 +05:30
endif singleRun
2009-12-22 17:58:02 +05:30
2013-04-29 16:47:30 +05:30
NiterationCrystallite = 0_pInt
numerics_integrationMode = 1_pInt
2013-05-17 23:22:46 +05:30
cutbackLooping : do while ( any ( crystallite_todo ( : , startIP : endIP , FEsolving_execELem ( 1 ) : FEsolving_execElem ( 2 ) ) ) )
timeSyncing1 : if ( any ( . not . crystallite_localPlasticity ) . and . numerics_timeSyncing ) then
2014-06-17 00:49:38 +05:30
2012-11-28 00:06:55 +05:30
! Time synchronization can only be used for nonlocal calculations, and only there it makes sense.
2014-08-26 20:14:32 +05:30
! The idea is that in nonlocal calculations often the vast majority of the ips
! converges in one iteration whereas a small fraction of ips has to do a lot of cutbacks.
2012-11-28 00:06:55 +05:30
! Hence, we try to minimize the computational effort by just doing a lot of cutbacks
! in the vicinity of the "bad" ips and leave the easily converged volume more or less as it is.
2014-08-26 20:14:32 +05:30
! However, some synchronization of the time step has to be done at the border between "bad" ips
! and the ones that immediately converged.
2012-11-28 00:06:55 +05:30
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i6)' ) '<< CRYST >> crystallite iteration ' , NiterationCrystallite
2012-11-28 00:06:55 +05:30
2014-08-26 20:14:32 +05:30
if ( any ( crystallite_syncSubFrac ) ) then
2013-04-29 16:47:30 +05:30
! Just did a time synchronization.
2014-08-26 20:14:32 +05:30
! If all synchronizers converged, then do nothing else than winding them forward.
! If any of the synchronizers did not converge, something went completely wrong
2013-04-29 16:47:30 +05:30
! and its not clear how to fix this, so all nonlocals become terminally ill.
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
if ( any ( crystallite_syncSubFrac . and . . not . crystallite_converged ( 1 , : , : ) ) ) then
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) then
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
2014-05-27 20:16:03 +05:30
if ( crystallite_syncSubFrac ( i , e ) . and . . not . crystallite_converged ( 1 , i , e ) ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i8,1x,i2)' ) '<< CRYST >> time synchronization: failed at el,ip ' , e , i
enddo
enddo
endif
crystallite_syncSubFrac = . false .
where ( . not . crystallite_localPlasticity )
crystallite_substep = 0.0_pReal
crystallite_todo = . false .
endwhere
else
!$OMP PARALLEL DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
crystallite_clearToWindForward ( i , e ) = crystallite_localPlasticity ( 1 , i , e ) . or . crystallite_syncSubFrac ( i , e )
crystallite_clearToCutback ( i , e ) = crystallite_localPlasticity ( 1 , i , e )
enddo
enddo
!$OMP END PARALLEL DO
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i6)' ) '<< CRYST >> time synchronization: wind forward'
endif
2012-11-28 00:06:55 +05:30
2014-08-26 20:14:32 +05:30
elseif ( any ( crystallite_syncSubFracCompleted ) ) then
2013-04-29 16:47:30 +05:30
! Just completed a time synchronization.
2014-08-26 20:14:32 +05:30
! Make sure that the ips that synchronized their time step start non-converged
2013-04-29 16:47:30 +05:30
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
if ( crystallite_syncSubFracCompleted ( i , e ) ) crystallite_converged ( 1 , i , e ) = . false .
crystallite_syncSubFracCompleted ( i , e ) = . false .
crystallite_clearToWindForward ( i , e ) = crystallite_localPlasticity ( 1 , i , e )
crystallite_clearToCutback ( i , e ) = crystallite_localPlasticity ( 1 , i , e ) . or . . not . crystallite_converged ( 1 , i , e )
enddo
enddo
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i6)' ) '<< CRYST >> time synchronization: done, proceed with cutback'
else
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
! Normal calculation.
! If all converged and are at the end of the time increment, then just do a final wind forward.
! If all converged, but not all reached the end of the time increment, then we only wind
! those forward that are still on their way, all others have to wait.
2014-08-26 20:14:32 +05:30
! If some did not converge and all are still at the start of the time increment,
2013-04-29 16:47:30 +05:30
! then all non-convergers force their converged neighbors to also do a cutback.
2014-08-26 20:14:32 +05:30
! In case that some ips have already wound forward to an intermediate time (subfrac),
2013-04-29 16:47:30 +05:30
! then all those ips that converged in the first iteration, but now have a non-converged neighbor
! have to synchronize their time step to the same intermediate time. If such a synchronization
2014-08-26 20:14:32 +05:30
! takes place, all other ips have to wait and only the synchronizers do a cutback. In the next
! iteration those will do a wind forward while all others still wait.
2013-04-29 16:47:30 +05:30
!$OMP PARALLEL DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
crystallite_clearToWindForward ( i , e ) = crystallite_localPlasticity ( 1 , i , e )
crystallite_clearToCutback ( i , e ) = crystallite_localPlasticity ( 1 , i , e )
enddo
enddo
!$OMP END PARALLEL DO
if ( all ( crystallite_localPlasticity . or . crystallite_converged ) ) then
if ( all ( crystallite_localPlasticity . or . crystallite_subStep + crystallite_subFrac > = 1.0_pReal ) ) then
crystallite_clearToWindForward = . true . ! final wind forward
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i6)' ) '<< CRYST >> final wind forward'
else
!$OMP PARALLEL DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
crystallite_clearToWindForward ( i , e ) = crystallite_localPlasticity ( 1 , i , e ) . or . crystallite_subStep ( 1 , i , e ) < 1.0_pReal
enddo
enddo
!$OMP END PARALLEL DO
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i6)' ) '<< CRYST >> wind forward'
endif
else
subFracIntermediate = maxval ( crystallite_subFrac , mask = . not . crystallite_localPlasticity )
if ( subFracIntermediate == 0.0_pReal ) then
crystallite_neighborEnforcedCutback = . false . ! look for ips that require a cutback because of a nonconverged neighbor
2014-08-26 20:14:32 +05:30
!$OMP PARALLEL
2013-04-29 16:47:30 +05:30
!$OMP DO PRIVATE(neighboring_e,neighboring_i)
2014-08-26 20:14:32 +05:30
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
2013-04-29 16:47:30 +05:30
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
if ( . not . crystallite_localPlasticity ( 1 , i , e ) . and . crystallite_converged ( 1 , i , e ) ) then
do n = 1_pInt , FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , e ) ) ) )
neighboring_e = mesh_ipNeighborhood ( 1 , n , i , e )
neighboring_i = mesh_ipNeighborhood ( 2 , n , i , e )
if ( neighboring_e > 0_pInt . and . neighboring_i > 0_pInt ) then
if ( . not . crystallite_localPlasticity ( 1 , neighboring_i , neighboring_e ) &
2014-08-26 20:14:32 +05:30
. and . . not . crystallite_converged ( 1 , neighboring_i , neighboring_e ) ) then
2013-04-29 16:47:30 +05:30
crystallite_neighborEnforcedCutback ( i , e ) = . true .
2012-11-28 00:06:55 +05:30
#ifndef _OPENMP
2013-04-29 16:47:30 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
write ( 6 , '(a12,i5,1x,i2,a,i5,1x,i2)' ) '<< CRYST >> ' , neighboring_e , neighboring_i , &
2012-11-28 00:06:55 +05:30
' enforced cutback at ' , e , i
#endif
2013-04-29 16:47:30 +05:30
exit
endif
endif
enddo
endif
enddo
enddo
!$OMP END DO
!$OMP DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
if ( crystallite_neighborEnforcedCutback ( i , e ) ) crystallite_converged ( 1 , i , e ) = . false .
enddo
enddo
!$OMP END DO
!$OMP END PARALLEL
else
crystallite_syncSubFrac = . false . ! look for ips that have to do a time synchronization because of a nonconverged neighbor
2014-08-26 20:14:32 +05:30
!$OMP PARALLEL
2013-04-29 16:47:30 +05:30
!$OMP DO PRIVATE(neighboring_e,neighboring_i)
2014-08-26 20:14:32 +05:30
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
2013-11-21 16:28:41 +05:30
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
if ( . not . crystallite_localPlasticity ( 1 , i , e ) . and . crystallite_subFrac ( 1 , i , e ) == 0.0_pReal ) then
do n = 1_pInt , FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , e ) ) ) )
neighboring_e = mesh_ipNeighborhood ( 1 , n , i , e )
neighboring_i = mesh_ipNeighborhood ( 2 , n , i , e )
if ( neighboring_e > 0_pInt . and . neighboring_i > 0_pInt ) then
if ( . not . crystallite_localPlasticity ( 1 , neighboring_i , neighboring_e ) &
2014-08-26 20:14:32 +05:30
. and . . not . crystallite_converged ( 1 , neighboring_i , neighboring_e ) ) then
2013-11-21 16:28:41 +05:30
crystallite_syncSubFrac ( i , e ) = . true .
2012-11-28 00:06:55 +05:30
#ifndef _OPENMP
2013-11-21 16:28:41 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
write ( 6 , '(a12,i5,1x,i2,a,i5,1x,i2)' ) '<< CRYST >> ' , neighboring_e , neighboring_i , &
' enforced time synchronization at ' , e , i
2012-11-28 00:06:55 +05:30
#endif
2013-11-21 16:28:41 +05:30
exit
2013-04-29 16:47:30 +05:30
endif
2013-11-21 16:28:41 +05:30
endif
enddo
endif
2013-04-29 16:47:30 +05:30
enddo
2013-11-21 16:28:41 +05:30
enddo
2013-04-29 16:47:30 +05:30
!$OMP END DO
!$OMP DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
if ( crystallite_syncSubFrac ( i , e ) ) crystallite_converged ( 1 , i , e ) = . false .
enddo
enddo
!$OMP END DO
!$OMP END PARALLEL
endif
where ( . not . crystallite_localPlasticity . and . crystallite_subStep < 1.0_pReal ) &
crystallite_converged = . false .
if ( any ( crystallite_syncSubFrac ) ) then ! have to do syncing now, so all wait except for the synchronizers which do a cutback
!$OMP PARALLEL DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
crystallite_clearToWindForward ( i , e ) = crystallite_localPlasticity ( 1 , i , e )
crystallite_clearToCutback ( i , e ) = crystallite_localPlasticity ( 1 , i , e ) . or . crystallite_syncSubFrac ( i , e )
enddo
enddo
!$OMP END PARALLEL DO
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i6)' ) '<< CRYST >> time synchronization: cutback'
else
!$OMP PARALLEL DO PRIVATE(myNgrains)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
if ( . not . crystallite_converged ( 1 , i , e ) ) crystallite_clearToCutback ( i , e ) = . true .
enddo
enddo
!$OMP END PARALLEL DO
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i6)' ) '<< CRYST >> cutback'
endif
endif
endif
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
! Make sure that all cutbackers start with the same substep
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
where ( . not . crystallite_localPlasticity . and . . not . crystallite_converged ) &
crystallite_subStep = minval ( crystallite_subStep , mask = . not . crystallite_localPlasticity &
. and . . not . crystallite_converged )
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
! Those that do neither wind forward nor cutback are not to do
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
!$OMP PARALLEL DO PRIVATE(myNgrains)
2013-10-19 00:27:28 +05:30
elementLooping2 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
2013-04-29 16:47:30 +05:30
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
if ( . not . crystallite_clearToWindForward ( i , e ) . and . . not . crystallite_clearToCutback ( i , e ) ) &
crystallite_todo ( 1 , i , e ) = . false .
enddo
2013-10-19 00:27:28 +05:30
enddo elementLooping2
2013-04-29 16:47:30 +05:30
!$OMP END PARALLEL DO
2014-08-26 20:14:32 +05:30
2013-05-17 23:22:46 +05:30
endif timeSyncing1
2013-04-29 16:47:30 +05:30
!$OMP PARALLEL DO PRIVATE(myNgrains,formerSubStep)
2013-10-19 00:27:28 +05:30
elementLooping3 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
2013-04-29 16:47:30 +05:30
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e ) ! iterate over IPs of this element to be processed
do g = 1 , myNgrains
! --- wind forward ---
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
if ( crystallite_converged ( g , i , e ) . and . crystallite_clearToWindForward ( i , e ) ) then
formerSubStep = crystallite_subStep ( g , i , e )
crystallite_subFrac ( g , i , e ) = crystallite_subFrac ( g , i , e ) + crystallite_subStep ( g , i , e )
!$OMP FLUSH(crystallite_subFrac)
crystallite_subStep ( g , i , e ) = min ( 1.0_pReal - crystallite_subFrac ( g , i , e ) , &
stepIncreaseCryst * crystallite_subStep ( g , i , e ) )
!$OMP FLUSH(crystallite_subStep)
if ( crystallite_subStep ( g , i , e ) > 0.0_pReal ) then
crystallite_subF0 ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) ! ...def grad
!$OMP FLUSH(crystallite_subF0)
crystallite_subLp0 ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) ! ...plastic velocity gradient
2014-09-03 01:16:52 +05:30
crystallite_subFp0 ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) ! ...plastic def grad
crystallite_subFe0 ( 1 : 3 , 1 : 3 , g , i , e ) = math_mul33x33 ( crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) ) ! only needed later on for stiffness calculation
2014-05-27 20:16:03 +05:30
!if abbrevation, make c and p private in omp
2014-05-12 18:30:37 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) )
2014-06-25 04:51:25 +05:30
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
2014-09-03 01:16:52 +05:30
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) )
2013-04-29 16:47:30 +05:30
crystallite_subTstar0_v ( 1 : 6 , g , i , e ) = crystallite_Tstar_v ( 1 : 6 , g , i , e ) ! ...2nd PK stress
if ( crystallite_syncSubFrac ( i , e ) ) then ! if we just did a synchronization of states, then we wind forward without any further time integration
crystallite_syncSubFracCompleted ( i , e ) = . true .
crystallite_syncSubFrac ( i , e ) = . false .
crystallite_todo ( g , i , e ) = . false .
else
crystallite_todo ( g , i , e ) = . true .
endif
!$OMP FLUSH(crystallite_todo)
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-04-29 16:47:30 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
2013-10-19 00:27:28 +05:30
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) &
write ( 6 , '(a,f12.8,a,f12.8,a,i8,1x,i2,1x,i3,/)' ) '<< CRYST >> winding forward from ' , &
2013-04-29 16:47:30 +05:30
crystallite_subFrac ( g , i , e ) - formerSubStep , ' to current crystallite_subfrac ' , &
crystallite_subFrac ( g , i , e ) , ' in crystallite_stressAndItsTangent at el ip g ' , e , i , g
2011-03-29 12:57:19 +05:30
#endif
2013-08-02 13:29:55 +05:30
else ! this crystallite just converged for the entire timestep
2013-04-29 16:47:30 +05:30
crystallite_todo ( g , i , e ) = . false . ! so done here
!$OMP FLUSH(crystallite_todo)
2013-08-02 11:48:41 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt &
. and . formerSubStep > 0.0_pReal ) then
2013-04-29 16:47:30 +05:30
!$OMP CRITICAL (distributionCrystallite)
debug_CrystalliteLoopDistribution ( min ( nCryst + 1_pInt , NiterationCrystallite ) ) = &
debug_CrystalliteLoopDistribution ( min ( nCryst + 1_pInt , NiterationCrystallite ) ) + 1_pInt
!$OMP END CRITICAL (distributionCrystallite)
endif
endif
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
! --- cutback ---
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
elseif ( . not . crystallite_converged ( g , i , e ) . and . crystallite_clearToCutback ( i , e ) ) then
if ( crystallite_syncSubFrac ( i , e ) ) then ! synchronize time
crystallite_subStep ( g , i , e ) = subFracIntermediate
else
crystallite_subStep ( g , i , e ) = subStepSizeCryst * crystallite_subStep ( g , i , e ) ! cut step in half and restore...
endif
!$OMP FLUSH(crystallite_subStep)
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subFp0 ( 1 : 3 , 1 : 3 , g , i , e ) ! ...plastic def grad
!$OMP FLUSH(crystallite_Fp)
crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) = math_inv33 ( crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) )
!$OMP FLUSH(crystallite_invFp)
crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subLp0 ( 1 : 3 , 1 : 3 , g , i , e ) ! ...plastic velocity grad
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
2013-04-29 16:47:30 +05:30
crystallite_Tstar_v ( 1 : 6 , g , i , e ) = crystallite_subTstar0_v ( 1 : 6 , g , i , e ) ! ...2nd PK stress
2014-05-27 20:16:03 +05:30
2013-04-29 16:47:30 +05:30
! cant restore dotState here, since not yet calculated in first cutback after initialization
crystallite_todo ( g , i , e ) = crystallite_subStep ( g , i , e ) > subStepMinCryst ! still on track or already done (beyond repair)
!$OMP FLUSH(crystallite_todo)
2012-11-22 15:28:36 +05:30
#ifndef _OPENMP
2014-08-26 20:14:32 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
2013-04-29 16:47:30 +05:30
if ( crystallite_todo ( g , i , e ) ) then
2014-07-10 14:17:00 +05:30
write ( 6 , '(a,f12.8,a,i8,1x,i2,1x,i3,/)' ) ' < < CRYST > > cutback step in crystallite_stressAndItsTangent &
2013-04-29 16:47:30 +05:30
& with new crystallite_subStep : ' , &
crystallite_subStep ( g , i , e ) , ' at el ip g ' , e , i , g
else
2014-07-10 14:17:00 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i3,/)' ) ' < < CRYST > > reached minimum step size &
2013-04-29 16:47:30 +05:30
& in crystallite_stressAndItsTangent at el ip g ' , e , i , g
endif
endif
2012-11-22 15:28:36 +05:30
#endif
2013-04-29 16:47:30 +05:30
endif
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
! --- prepare for integration ---
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
if ( crystallite_todo ( g , i , e ) . and . ( crystallite_clearToWindForward ( i , e ) . or . crystallite_clearToCutback ( i , e ) ) ) then
crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subF0 ( 1 : 3 , 1 : 3 , g , i , e ) &
+ crystallite_subStep ( g , i , e ) &
* ( crystallite_partionedF ( 1 : 3 , 1 : 3 , g , i , e ) &
- crystallite_partionedF0 ( 1 : 3 , 1 : 3 , g , i , e ) )
!$OMP FLUSH(crystallite_subF)
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) = math_mul33x33 ( crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) , crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) )
crystallite_subdt ( g , i , e ) = crystallite_subStep ( g , i , e ) * crystallite_dt ( g , i , e )
crystallite_converged ( g , i , e ) = . false . ! start out non-converged
endif
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
enddo ! grains
enddo ! IPs
2013-10-19 00:27:28 +05:30
enddo elementLooping3
2013-04-29 16:47:30 +05:30
!$OMP END PARALLEL DO
2014-08-26 20:14:32 +05:30
2013-05-17 23:22:46 +05:30
timeSyncing2 : if ( numerics_timeSyncing ) then
2013-04-29 16:47:30 +05:30
if ( any ( . not . crystallite_localPlasticity . and . . not . crystallite_todo . and . . not . crystallite_converged &
. and . crystallite_subStep < = subStepMinCryst ) ) then ! no way of rescuing a nonlocal ip that violated the lower time step limit, ...
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) then
2013-10-19 00:27:28 +05:30
elementLooping4 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
2013-04-29 16:47:30 +05:30
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
do g = 1 , myNgrains
if ( . not . crystallite_localPlasticity ( g , i , e ) . and . . not . crystallite_todo ( g , i , e ) &
2014-05-27 20:16:03 +05:30
. and . . not . crystallite_converged ( g , i , e ) . and . crystallite_subStep ( g , i , e ) < = subStepMinCryst ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i3)' ) '<< CRYST >> nonlocal violated minimum subStep at el,ip,g ' , e , i , g
enddo
enddo
2013-10-19 00:27:28 +05:30
enddo elementLooping4
2013-04-29 16:47:30 +05:30
endif
where ( . not . crystallite_localPlasticity )
crystallite_todo = . false . ! ... so let all nonlocal ips die peacefully
crystallite_subStep = 0.0_pReal
endwhere
endif
2014-08-26 20:14:32 +05:30
endif timeSyncing2
2013-04-29 16:47:30 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) then
write ( 6 , '(/,a,e12.5)' ) '<< CRYST >> min(subStep) ' , minval ( crystallite_subStep )
write ( 6 , '(a,e12.5)' ) '<< CRYST >> max(subStep) ' , maxval ( crystallite_subStep )
write ( 6 , '(a,e12.5)' ) '<< CRYST >> min(subFrac) ' , minval ( crystallite_subFrac )
write ( 6 , '(a,e12.5,/)' ) '<< CRYST >> max(subFrac) ' , maxval ( crystallite_subFrac )
2014-05-27 20:16:03 +05:30
flush ( 6 )
2013-04-29 16:47:30 +05:30
endif
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
! --- integrate --- requires fully defined state array (basic + dependent state)
2014-05-27 20:16:03 +05:30
2013-04-29 16:47:30 +05:30
if ( any ( crystallite_todo ) ) then
select case ( numerics_integrator ( numerics_integrationMode ) )
case ( 1_pInt )
call crystallite_integrateStateFPI ( )
case ( 2_pInt )
call crystallite_integrateStateEuler ( )
case ( 3_pInt )
call crystallite_integrateStateAdaptiveEuler ( )
case ( 4_pInt )
call crystallite_integrateStateRK4 ( )
case ( 5_pInt )
call crystallite_integrateStateRKCK45 ( )
end select
endif
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
where ( . not . crystallite_converged . and . crystallite_subStep > subStepMinCryst ) & ! do not try non-converged & fully cutbacked any further
crystallite_todo = . true .
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
NiterationCrystallite = NiterationCrystallite + 1_pInt
2014-08-26 20:14:32 +05:30
2013-04-29 16:47:30 +05:30
enddo cutbackLooping
2010-11-03 22:52:48 +05:30
! --+>> CHECK FOR NON-CONVERGED CRYSTALLITES <<+--
2013-11-21 16:28:41 +05:30
2013-10-19 00:27:28 +05:30
elementLooping5 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
2013-05-17 23:22:46 +05:30
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e ) ! iterate over IPs of this element to be processed
do g = 1 , myNgrains
if ( . not . crystallite_converged ( g , i , e ) ) then ! respond fully elastically (might be not required due to becoming terminally ill anyway)
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) &
2014-08-27 21:24:11 +05:30
write ( 6 , '(a,i8,1x,a,i8,a,1x,i2,1x,i3,/)' ) '<< CRYST >> no convergence: respond fully elastic at el (elFE) ip g ' , &
e , '(' , mesh_element ( 1 , e ) , ')' , i , g
2013-05-17 23:22:46 +05:30
invFp = math_inv33 ( crystallite_partionedFp0 ( 1 : 3 , 1 : 3 , g , i , e ) )
Fe_guess = math_mul33x33 ( crystallite_partionedF ( 1 : 3 , 1 : 3 , g , i , e ) , invFp )
call constitutive_TandItsTangent ( Tstar , junk2 , Fe_guess , g , i , e )
crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) = math_mul33x33 ( Fe_guess , math_mul33x33 ( Tstar , transpose ( invFp ) ) )
endif
2014-08-26 20:14:32 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
2012-11-07 21:13:29 +05:30
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
2013-05-17 23:22:46 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i3)' ) '<< CRYST >> central solution of cryst_StressAndTangent at el ip g ' , e , i , g
write ( 6 , '(/,a,/,3(12x,3(f12.4,1x)/))' ) '<< CRYST >> P / MPa' , &
2014-08-27 21:24:11 +05:30
math_transpose33 ( crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) ) * 1.0e-6_pReal
2013-05-17 23:22:46 +05:30
write ( 6 , '(a,/,3(12x,3(f14.9,1x)/))' ) '<< CRYST >> Fp' , &
math_transpose33 ( crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) )
write ( 6 , '(a,/,3(12x,3(f14.9,1x)/),/)' ) '<< CRYST >> Lp' , &
math_transpose33 ( crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) )
2014-05-27 20:16:03 +05:30
flush ( 6 )
2013-05-17 23:22:46 +05:30
endif
enddo
enddo
2013-10-19 00:27:28 +05:30
enddo elementLooping5
2010-11-03 22:52:48 +05:30
2014-09-03 01:16:52 +05:30
2010-11-03 22:52:48 +05:30
! --+>> STIFFNESS CALCULATION <<+--
2009-06-16 14:33:30 +05:30
2013-10-19 00:27:28 +05:30
computeJacobian : if ( updateJaco ) then
jacobianMethod : if ( analyticJaco ) then
2009-12-15 13:50:31 +05:30
2013-11-21 16:28:41 +05:30
! --- ANALYTIC JACOBIAN ---
2014-08-08 02:38:34 +05:30
!$OMP PARALLEL DO PRIVATE(dFedF,dSdF,dSdFe,dLpdS,dFpinvdF,rhs_3333,lhs_3333,temp_3333,temp_99,junk,myNgrains)
2013-11-21 16:28:41 +05:30
elementLooping6 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e ) ! iterate over IPs of this element to be processed
do g = 1_pInt , myNgrains
2014-08-08 02:38:34 +05:30
call constitutive_TandItsTangent ( junk , dSdFe , crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! call constitutive law to calculate 2nd Piola-Kirchhoff stress and its derivative
call constitutive_LpAndItsTangent ( junk , temp_99 , crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-10-10 17:58:57 +05:30
g , i , e )
2014-08-08 02:38:34 +05:30
dLpdS = reshape ( temp_99 , shape = [ 3 , 3 , 3 , 3 ] )
rhs_3333 = 0.0_pReal
2013-11-21 16:28:41 +05:30
forall ( p = 1_pInt : 3_pInt , o = 1_pInt : 3_pInt ) &
2014-08-08 02:38:34 +05:30
rhs_3333 ( p , o , 1 : 3 , 1 : 3 ) = math_mul33x33 ( dSdFe ( p , o , 1 : 3 , 1 : 3 ) , &
math_transpose33 ( crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) ) )
junk = math_mul33x33 ( math_mul33x33 ( crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) ) , &
math_inv33 ( crystallite_Fp0 ( 1 : 3 , 1 : 3 , g , i , e ) ) )
temp_3333 = 0.0_pReal
2013-11-21 16:28:41 +05:30
forall ( p = 1_pInt : 3_pInt , o = 1_pInt : 3_pInt ) &
2014-08-08 02:38:34 +05:30
temp_3333 ( 1 : 3 , 1 : 3 , p , o ) = math_mul33x33 ( junk , dLpdS ( 1 : 3 , 1 : 3 , p , o ) )
lhs_3333 = crystallite_dt ( g , i , e ) * math_mul3333xx3333 ( dSdFe , temp_3333 )
call math_invert ( 9_pInt , math_identity2nd ( 9_pInt ) + reshape ( lhs_3333 , shape = [ 9 , 9 ] ) , temp_99 , error )
if ( error ) call IO_error ( error_ID = 400_pInt , ext_msg = 'analytic tangent inversion' )
dSdF = math_mul3333xx3333 ( reshape ( temp_99 , shape = [ 3 , 3 , 3 , 3 ] ) , rhs_3333 )
temp_3333 = math_mul3333xx3333 ( dLpdS , dSdF )
dFpinvdF = 0.0_pReal
2014-01-22 21:04:10 +05:30
forall ( p = 1_pInt : 3_pInt , o = 1_pInt : 3_pInt ) &
2014-08-08 02:38:34 +05:30
dFpinvdF ( 1 : 3 , 1 : 3 , p , o ) = - crystallite_dt ( g , i , e ) * &
math_mul33x33 ( math_inv33 ( crystallite_Fp0 ( 1 : 3 , 1 : 3 , g , i , e ) ) , &
temp_3333 ( 1 : 3 , 1 : 3 , p , o ) )
temp_3333 = 0.0_pReal
2014-01-22 21:04:10 +05:30
forall ( p = 1_pInt : 3_pInt , o = 1_pInt : 3_pInt ) &
2014-08-08 02:38:34 +05:30
temp_3333 ( o , p , o , 1 : 3 ) = crystallite_invFp ( 1 : 3 , p , g , i , e ) ! dFe^T_ij/dF_kl = delta_jk * (Fp current^-1)_li
dFedF = 0.0_pReal
2014-01-22 21:04:10 +05:30
forall ( p = 1_pInt : 3_pInt , o = 1_pInt : 3_pInt ) &
2014-08-08 02:38:34 +05:30
dFedF ( 1 : 3 , 1 : 3 , p , o ) = temp_3333 ( 1 : 3 , 1 : 3 , p , o ) + &
2014-08-15 14:34:00 +05:30
math_mul33x33 ( crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) , &
2014-08-26 20:14:32 +05:30
dFpinvdF ( 1 : 3 , 1 : 3 , p , o ) )
2014-01-22 21:04:10 +05:30
2014-08-08 02:38:34 +05:30
forall ( p = 1_pInt : 3_pInt , o = 1_pInt : 3_pInt ) &
crystallite_dPdF ( 1 : 3 , 1 : 3 , o , p , g , i , e ) = &
math_mul33x33 ( math_mul33x33 ( dFedF ( 1 : 3 , 1 : 3 , o , p ) , &
math_Mandel6to33 ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) ) ) , &
2014-08-10 15:57:35 +05:30
math_transpose33 ( crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) ) ) + & ! dP/dF = dFe/dF * S * Fp^-T...
math_mul33x33 ( crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2014-08-08 02:38:34 +05:30
math_mul33x33 ( dSdF ( 1 : 3 , 1 : 3 , o , p ) , &
2014-08-26 20:14:32 +05:30
math_transpose33 ( crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) ) ) ) + & ! + Fe * dS/dF * Fp^-T
2014-08-10 15:57:35 +05:30
math_mul33x33 ( crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2014-08-08 02:38:34 +05:30
math_mul33x33 ( math_Mandel6to33 ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) ) , &
2014-08-26 20:14:32 +05:30
math_transpose33 ( dFpinvdF ( 1 : 3 , 1 : 3 , p , o ) ) ) ) ! + Fe * S * dFp^-T/dF
2014-08-08 02:38:34 +05:30
enddo ; enddo
enddo elementLooping6
!$OMP END PARALLEL DO
2013-11-21 16:28:41 +05:30
else jacobianMethod
2014-08-26 20:14:32 +05:30
2013-11-21 16:28:41 +05:30
! --- STANDARD (PERTURBATION METHOD) FOR JACOBIAN ---
numerics_integrationMode = 2_pInt
2014-08-26 20:14:32 +05:30
2013-11-21 16:28:41 +05:30
! --- BACKUP ---
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL DO PRIVATE(myNgrains)
elementLooping7 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains )
2014-09-03 01:16:52 +05:30
2014-05-27 20:16:03 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) )
2014-06-25 04:51:25 +05:30
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
2014-09-03 01:16:52 +05:30
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) )
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) )
2014-06-25 04:51:25 +05:30
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
2014-09-03 01:16:52 +05:30
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) )
2014-07-02 17:57:39 +05:30
2014-05-27 20:16:03 +05:30
F_backup ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) ! ... and kinematics
Fp_backup ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e )
InvFp_backup ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e )
Fe_backup ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e )
Lp_backup ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e )
Tstar_v_backup ( 1 : 6 , g , i , e ) = crystallite_Tstar_v ( 1 : 6 , g , i , e )
P_backup ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_P ( 1 : 3 , 1 : 3 , g , i , e )
convergenceFlag_backup ( g , i , e ) = crystallite_converged ( g , i , e )
endforall
enddo elementLooping7
2014-08-26 20:14:32 +05:30
!$END PARALLEL DO
2013-11-21 16:28:41 +05:30
! --- CALCULATE STATE AND STRESS FOR PERTURBATION ---
dPdF_perturbation1 = crystallite_dPdF0 ! initialize stiffness with known good values from last increment
dPdF_perturbation2 = crystallite_dPdF0 ! initialize stiffness with known good values from last increment
2014-05-27 20:16:03 +05:30
pertubationLoop : do perturbation = 1 , 2 ! forward and backward perturbation
2013-11-21 16:28:41 +05:30
if ( iand ( pert_method , perturbation ) > 0_pInt ) then ! mask for desired direction
myPert = - pert_Fg * ( - 1.0_pReal ) ** perturbation ! set perturbation step
do k = 1 , 3 ; do l = 1 , 3 ! ...alter individual components
2014-08-26 20:14:32 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) &
2013-11-21 16:28:41 +05:30
write ( 6 , '(a,2(1x,i1),1x,a,/)' ) '<< CRYST >> [[[[[[ Stiffness perturbation' , k , l , ']]]]]]'
2014-08-26 20:14:32 +05:30
! --- INITIALIZE UNPERTURBED STATE ---
2013-11-21 16:28:41 +05:30
select case ( numerics_integrator ( numerics_integrationMode ) )
2014-05-27 20:16:03 +05:30
case ( 1_pInt )
!why not OMP? ! Fix-point method: restore to last converged state at end of subinc, since this is probably closest to perturbed state
2013-11-21 16:28:41 +05:30
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains )
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) = Fp_backup ( 1 : 3 , 1 : 3 , g , i , e )
2014-01-21 22:05:12 +05:30
crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) = InvFp_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) = Fe_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) = Lp_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Tstar_v ( 1 : 6 , g , i , e ) = Tstar_v_backup ( 1 : 6 , g , i , e )
2013-11-21 16:28:41 +05:30
endforall
enddo
2014-05-12 18:30:37 +05:30
case ( 2_pInt , 3_pInt ) ! explicit Euler methods: nothing to restore (except for F), since we are only doing a stress integration step
2014-08-26 20:14:32 +05:30
case ( 4_pInt , 5_pInt )
2014-05-27 20:16:03 +05:30
!why not OMP? ! explicit Runge-Kutta methods: restore to start of subinc, since we are doing a full integration of state and stress
2013-11-21 16:28:41 +05:30
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains )
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % subState0 ( : , mappingConstitutive ( 1 , g , i , e ) )
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subFp0 ( 1 : 3 , 1 : 3 , g , i , e )
2014-01-21 22:05:12 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subFe0 ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) = crystallite_subLp0 ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Tstar_v ( 1 : 6 , g , i , e ) = crystallite_subTstar0_v ( 1 : 6 , g , i , e )
2013-11-21 16:28:41 +05:30
endforall
enddo
end select
! --- PERTURB EITHER FORWARD OR BACKWARD ---
2014-05-27 20:16:03 +05:30
!why not OMP?
2014-01-21 21:39:00 +05:30
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
do g = 1 , myNgrains
crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) = F_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_subF ( k , l , g , i , e ) = crystallite_subF ( k , l , g , i , e ) + myPert
crystallite_todo ( g , i , e ) = crystallite_requested ( g , i , e ) &
. and . convergenceFlag_backup ( g , i , e )
2014-05-27 20:16:03 +05:30
if ( crystallite_todo ( g , i , e ) ) crystallite_converged ( g , i , e ) = . false . ! start out non-converged
2014-01-21 21:39:00 +05:30
enddo ; enddo ; enddo
2013-11-21 16:28:41 +05:30
2014-05-27 20:16:03 +05:30
2013-11-21 16:28:41 +05:30
select case ( numerics_integrator ( numerics_integrationMode ) )
case ( 1_pInt )
call crystallite_integrateStateFPI ( )
case ( 2_pInt )
call crystallite_integrateStateEuler ( )
case ( 3_pInt )
call crystallite_integrateStateAdaptiveEuler ( )
case ( 4_pInt )
call crystallite_integrateStateRK4 ( )
case ( 5_pInt )
call crystallite_integrateStateRKCK45 ( )
end select
2014-05-27 20:16:03 +05:30
!why not OMP?
2013-11-21 16:28:41 +05:30
elementLooping8 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
select case ( perturbation )
case ( 1_pInt )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains , &
2014-05-27 20:16:03 +05:30
crystallite_requested ( g , i , e ) . and . crystallite_converged ( g , i , e ) ) & ! converged state warrants stiffness update
dPdF_perturbation1 ( 1 : 3 , 1 : 3 , k , l , g , i , e ) = &
( crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) - P_backup ( 1 : 3 , 1 : 3 , g , i , e ) ) / myPert ! tangent dP_ij/dFg_kl
2013-11-21 16:28:41 +05:30
case ( 2_pInt )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains , &
2014-05-27 20:16:03 +05:30
crystallite_requested ( g , i , e ) . and . crystallite_converged ( g , i , e ) ) & ! converged state warrants stiffness update
dPdF_perturbation2 ( 1 : 3 , 1 : 3 , k , l , g , i , e ) = &
( crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) - P_backup ( 1 : 3 , 1 : 3 , g , i , e ) ) / myPert ! tangent dP_ij/dFg_kl
2013-11-21 16:28:41 +05:30
end select
enddo elementLooping8
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
enddo ; enddo ! k,l component perturbation loop
2013-11-21 16:28:41 +05:30
endif
2014-05-27 20:16:03 +05:30
enddo pertubationLoop
2013-11-21 16:28:41 +05:30
! --- STIFFNESS ACCORDING TO PERTURBATION METHOD AND CONVERGENCE ---
elementLooping9 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
select case ( pert_method )
case ( 1_pInt )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains , &
crystallite_requested ( g , i , e ) . and . convergenceFlag_backup ( g , i , e ) ) & ! perturbation mode 1: central solution converged
crystallite_dPdF ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) = dPdF_perturbation1 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e )
case ( 2_pInt )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains , &
crystallite_requested ( g , i , e ) . and . convergenceFlag_backup ( g , i , e ) ) & ! perturbation mode 2: central solution converged
crystallite_dPdF ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) = dPdF_perturbation2 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e )
case ( 3_pInt )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains , &
crystallite_requested ( g , i , e ) . and . convergenceFlag_backup ( g , i , e ) ) & ! perturbation mode 3: central solution converged
crystallite_dPdF ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) = 0.5_pReal * ( dPdF_perturbation1 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) &
+ dPdF_perturbation2 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) )
end select
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains , &
crystallite_requested ( g , i , e ) . and . . not . convergenceFlag_backup ( g , i , e ) ) & ! for any pertubation mode: if central solution did not converge...
crystallite_dPdF ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) = crystallite_fallbackdPdF ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , g , i , e ) ! ...use (elastic) fallback
enddo elementLooping9
! --- RESTORE ---
2014-05-27 20:16:03 +05:30
!why not OMP?
2013-11-21 16:28:41 +05:30
elementLooping10 : do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
forall ( i = FEsolving_execIP ( 1 , e ) : FEsolving_execIP ( 2 , e ) , g = 1 : myNgrains )
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % state_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = &
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % dotState_backup ( : , mappingConstitutive ( 1 , g , i , e ) )
2014-01-21 23:58:21 +05:30
crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) = F_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) = Fp_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) = InvFp_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) = Fe_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) = Lp_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_Tstar_v ( 1 : 6 , g , i , e ) = Tstar_v_backup ( 1 : 6 , g , i , e )
crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) = P_backup ( 1 : 3 , 1 : 3 , g , i , e )
crystallite_converged ( g , i , e ) = convergenceFlag_backup ( g , i , e )
2013-11-21 16:28:41 +05:30
endforall
enddo elementLooping10
2014-01-22 21:04:10 +05:30
endif jacobianMethod
2013-10-19 00:27:28 +05:30
endif computeJacobian
2014-05-27 20:16:03 +05:30
!why not OMP?
2013-10-19 00:27:28 +05:30
2012-03-09 01:55:28 +05:30
end subroutine crystallite_stressAndItsTangent
2009-05-07 21:57:36 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2014-08-26 20:14:32 +05:30
!> @brief integrate stress, state with 4th order explicit Runge Kutta method
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-04-26 18:53:36 +05:30
subroutine crystallite_integrateStateRK4 ( )
2013-10-19 00:27:28 +05:30
use numerics , only : &
numerics_integrationMode
use debug , only : &
debug_level , &
debug_crystallite , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_e , &
debug_i , &
debug_g , &
debug_StateLoopDistribution
use FEsolving , only : &
2014-08-26 20:14:32 +05:30
FEsolving_execElem , &
2013-10-19 00:27:28 +05:30
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_Ngrains , &
2014-05-12 18:30:37 +05:30
plasticState , &
2014-06-25 04:51:25 +05:30
damageState , &
thermalState , &
2014-06-23 00:28:29 +05:30
mappingConstitutive , &
2013-10-19 00:27:28 +05:30
homogenization_maxNgrains
use constitutive , only : &
2014-05-27 20:16:03 +05:30
constitutive_collectDotState , &
2014-06-23 00:28:29 +05:30
constitutive_microstructure
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
implicit none
2013-10-19 00:27:28 +05:30
real ( pReal ) , dimension ( 4 ) , parameter :: &
2014-05-27 20:16:03 +05:30
TIMESTEPFRACTION = [ 0.5_pReal , 0.5_pReal , 1.0_pReal , 1.0_pReal ] ! factor giving the fraction of the original timestep used for Runge Kutta Integration
2013-10-19 00:27:28 +05:30
real ( pReal ) , dimension ( 4 ) , parameter :: &
2014-09-03 01:16:52 +05:30
WEIGHT = [ 1.0_pReal , 2.0_pReal , 2.0_pReal , 1.0_pReal / 6.0_pReal ] ! weight of slope used for Runge Kutta integration (final weight divided by 6)
2013-04-26 18:53:36 +05:30
2014-05-27 20:16:03 +05:30
integer ( pInt ) :: e , & ! element index in element loop
2013-02-22 04:38:36 +05:30
i , & ! integration point index in ip loop
g , & ! grain index in grain loop
2014-05-27 20:16:03 +05:30
p , & ! phase loop
c , &
2013-02-22 04:38:36 +05:30
n , &
2014-06-25 04:51:25 +05:30
mySizePlasticDotState , &
mySizeDamageDotState , &
mySizeThermalDotState
2013-02-22 04:38:36 +05:30
integer ( pInt ) , dimension ( 2 ) :: eIter ! bounds for element iteration
integer ( pInt ) , dimension ( 2 , mesh_NcpElems ) :: iIter , & ! bounds for ip iteration
gIter ! bounds for grain iteration
2013-04-30 17:44:07 +05:30
logical :: singleRun ! flag indicating computation for single (g,i,e) triple
2014-08-26 20:14:32 +05:30
2013-04-26 18:53:36 +05:30
eIter = FEsolving_execElem ( 1 : 2 )
do e = eIter ( 1 ) , eIter ( 2 )
iIter ( 1 : 2 , e ) = FEsolving_execIP ( 1 : 2 , e )
gIter ( 1 : 2 , e ) = [ 1_pInt , homogenization_Ngrains ( mesh_element ( 3 , e ) ) ]
enddo
2014-08-26 20:14:32 +05:30
2013-04-30 17:44:07 +05:30
singleRun = ( eIter ( 1 ) == eIter ( 2 ) . and . iIter ( 1 , eIter ( 1 ) ) == iIter ( 2 , eIter ( 2 ) ) )
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
!--------------------------------------------------------------------------------------------------
! initialize dotState
if ( . not . singleRun ) then
forall ( p = 1_pInt : size ( plasticState ) ) plasticState ( p ) % RK4dotState = 0.0_pReal
2014-09-03 01:16:52 +05:30
forall ( p = 1_pInt : size ( damageState ) ) damageState ( p ) % RK4dotState = 0.0_pReal
2014-06-25 04:51:25 +05:30
forall ( p = 1_pInt : size ( thermalState ) ) thermalState ( p ) % RK4dotState = 0.0_pReal
2014-05-27 20:16:03 +05:30
else
e = eIter ( 1 )
i = iIter ( 1 , e )
do g = iIter ( 1 , e ) , iIter ( 2 , e )
2014-09-03 01:16:52 +05:30
plasticState ( mappingConstitutive ( 2 , g , i , e ) ) % RK4dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = 0.0_pReal
damageState ( mappingConstitutive ( 2 , g , i , e ) ) % RK4dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = 0.0_pReal
thermalState ( mappingConstitutive ( 2 , g , i , e ) ) % RK4dotState ( : , mappingConstitutive ( 1 , g , i , e ) ) = 0.0_pReal
2014-05-27 20:16:03 +05:30
enddo
endif
!--------------------------------------------------------------------------------------------------
! first Runge-Kutta step
!$OMP PARALLEL
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
crystallite_subdt ( g , i , e ) , crystallite_subFrac , g , i , e )
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
!$OMP DO PRIVATE(p,c)
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2013-02-22 04:38:36 +05:30
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
2014-09-03 01:16:52 +05:30
c = mappingConstitutive ( 1 , g , i , e )
p = mappingConstitutive ( 2 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , c ) / = plasticState ( p ) % dotState ( : , c ) ) . or . &
any ( damageState ( p ) % dotState ( : , c ) / = damageState ( p ) % dotState ( : , c ) ) . or . &
any ( thermalState ( p ) % dotState ( : , c ) / = thermalState ( p ) % dotState ( : , c ) ) ) then ! NaN occured in dotState
2014-05-27 20:16:03 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
2013-02-22 04:38:36 +05:30
!$OMP CRITICAL (checkTodo)
2014-05-27 20:16:03 +05:30
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
2013-02-22 04:38:36 +05:30
!$OMP END CRITICAL (checkTodo)
2014-05-27 20:16:03 +05:30
else ! if broken local...
crystallite_todo ( g , i , e ) = . false . ! ... skip this one next time
2013-02-22 04:38:36 +05:30
endif
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
!$OMP END PARALLEL
2014-05-27 20:16:03 +05:30
!--------------------------------------------------------------------------------------------------
2014-08-26 20:14:32 +05:30
! --- SECOND TO FOURTH RUNGE KUTTA STEP PLUS FINAL INTEGRATION ---
2014-05-27 20:16:03 +05:30
2013-02-22 04:38:36 +05:30
do n = 1_pInt , 4_pInt
! --- state update ---
2014-08-26 20:14:32 +05:30
!$OMP PARALLEL
2014-05-27 20:16:03 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
2014-05-27 20:16:03 +05:30
c = mappingConstitutive ( 1 , g , i , e )
2014-09-03 01:16:52 +05:30
plasticState ( p ) % RK4dotState ( : , c ) = plasticState ( p ) % RK4dotState ( : , c ) &
+ weight ( n ) * plasticState ( p ) % dotState ( : , c )
damageState ( p ) % RK4dotState ( : , c ) = damageState ( p ) % RK4dotState ( : , c ) &
+ weight ( n ) * damageState ( p ) % dotState ( : , c )
thermalState ( p ) % RK4dotState ( : , c ) = thermalState ( p ) % RK4dotState ( : , c ) &
+ weight ( n ) * thermalState ( p ) % dotState ( : , c )
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
2014-08-26 20:14:32 +05:30
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
2014-09-03 01:16:52 +05:30
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-07-02 17:57:39 +05:30
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
mySizeDamageDotState = damageState ( p ) % sizeDotState
mySizeThermalDotState = thermalState ( p ) % sizeDotState
2014-09-03 01:41:57 +05:30
plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) = plasticState ( p ) % subState0 ( 1 : mySizePlasticDotState , c ) &
2014-06-25 04:51:25 +05:30
+ plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , c ) &
* crystallite_subdt ( g , i , e ) * timeStepFraction ( n )
2014-09-03 01:41:57 +05:30
damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) = damageState ( p ) % subState0 ( 1 : mySizeDamageDotState , c ) &
2014-06-25 04:51:25 +05:30
+ damageState ( p ) % dotState ( 1 : mySizeDamageDotState , c ) &
* crystallite_subdt ( g , i , e ) * timeStepFraction ( n )
2014-09-03 01:41:57 +05:30
thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) = thermalState ( p ) % subState0 ( 1 : mySizeThermalDotState , c ) &
2014-06-25 04:51:25 +05:30
+ thermalState ( p ) % dotState ( 1 : mySizeThermalDotState , c ) &
* crystallite_subdt ( g , i , e ) * timeStepFraction ( n )
2014-09-03 01:16:52 +05:30
2012-06-06 20:41:30 +05:30
#ifndef _OPENMP
2014-09-03 01:16:52 +05:30
if ( n == 4 &
. and . iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then ! final integration step
2014-07-02 17:57:39 +05:30
2014-09-03 01:16:52 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i3,/)' ) '<< CRYST >> updateState at el ip g ' , e , i , g
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> dotState' , plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , c )
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> new state' , plasticState ( p ) % state ( 1 : mySizePlasticDotState , c )
2013-02-22 04:38:36 +05:30
endif
2014-09-03 01:16:52 +05:30
#endif
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
2014-08-26 20:14:32 +05:30
!$OMP ENDDO
2013-02-22 04:38:36 +05:30
! --- state jump ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_stateJump ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- update dependent states ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-10-10 17:58:57 +05:30
call constitutive_microstructure ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-09-03 01:16:52 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2014-06-25 04:51:25 +05:30
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! update dependent state variables to be consistent with basic states
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- stress integration ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_integrateStress ( g , i , e , timeStepFraction ( n ) ) ! fraction of original times step
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
2014-08-26 20:14:32 +05:30
!$OMP ENDDO
2013-02-22 04:38:36 +05:30
! --- dot state and RK dot state---
2014-09-03 01:16:52 +05:30
first3steps : if ( n < 4 ) then
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
timeStepFraction ( n ) * crystallite_subdt ( g , i , e ) , & ! fraction of original timestep
2013-02-22 04:38:36 +05:30
crystallite_subFrac , g , i , e )
enddo ; enddo ; enddo
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
2014-07-02 17:57:39 +05:30
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , c ) / = plasticState ( p ) % dotState ( : , c ) ) . or . &
2014-06-25 04:51:25 +05:30
any ( damageState ( p ) % dotState ( : , c ) / = damageState ( p ) % dotState ( : , c ) ) . or . &
2014-09-03 01:16:52 +05:30
any ( thermalState ( p ) % dotState ( : , c ) / = thermalState ( p ) % dotState ( : , c ) ) ) then ! NaN occured in dotState
2014-05-27 20:16:03 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
else ! if broken local...
crystallite_todo ( g , i , e ) = . false . ! ... skip this one next time
endif
endif
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-09-03 01:16:52 +05:30
endif first3steps
2014-05-27 20:16:03 +05:30
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
enddo
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- SET CONVERGENCE FLAG ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
crystallite_converged ( g , i , e ) = . true . ! if still "to do" then converged per definitionem
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
!$OMP CRITICAL (distributionState)
debug_StateLoopDistribution ( 4 , numerics_integrationMode ) = &
debug_StateLoopDistribution ( 4 , numerics_integrationMode ) + 1_pInt
!$OMP END CRITICAL (distributionState)
endif
endif
enddo ; enddo ; enddo
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- CHECK NONLOCAL CONVERGENCE ---
2014-08-26 20:14:32 +05:30
if ( . not . singleRun ) then ! if not requesting Integration of just a single IP
2013-02-22 04:38:36 +05:30
if ( any ( . not . crystallite_converged . and . . not . crystallite_localPlasticity ) ) then ! any non-local not yet converged (or broken)...
crystallite_converged = crystallite_converged . and . crystallite_localPlasticity ! ...restart all non-local as not converged
endif
endif
2014-08-26 20:14:32 +05:30
2012-03-09 01:55:28 +05:30
end subroutine crystallite_integrateStateRK4
2010-10-01 17:48:49 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2014-08-26 20:14:32 +05:30
!> @brief integrate stress, state with 5th order Runge-Kutta Cash-Karp method with
2013-02-22 04:38:36 +05:30
!> adaptive step size (use 5th order solution to advance = "local extrapolation")
!--------------------------------------------------------------------------------------------------
2013-04-26 18:53:36 +05:30
subroutine crystallite_integrateStateRKCK45 ( )
2013-11-21 16:28:41 +05:30
use debug , only : &
debug_level , &
debug_crystallite , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_e , &
debug_i , &
debug_g , &
debug_StateLoopDistribution
use numerics , only : &
rTol_crystalliteState , &
numerics_integrationMode
use FEsolving , only : &
2014-08-26 20:14:32 +05:30
FEsolving_execElem , &
2013-11-21 16:28:41 +05:30
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_Ngrains , &
2014-05-27 20:16:03 +05:30
plasticState , &
2014-06-25 04:51:25 +05:30
damageState , &
thermalState , &
2014-06-23 00:28:29 +05:30
mappingConstitutive , &
2013-11-21 16:28:41 +05:30
homogenization_maxNgrains
use constitutive , only : &
2014-05-27 20:16:03 +05:30
constitutive_collectDotState , &
2014-06-11 22:02:09 +05:30
constitutive_maxSizeDotState , &
2014-09-23 16:08:20 +05:30
constitutive_damage_maxSizeDotState , &
constitutive_thermal_maxSizeDotState , &
2013-11-21 16:28:41 +05:30
constitutive_microstructure
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
implicit none
2013-11-21 16:28:41 +05:30
real ( pReal ) , dimension ( 5 , 5 ) , parameter :: &
A = reshape ( [ &
. 2_pReal , . 075_pReal , . 3_pReal , - 1 1.0_pReal / 5 4.0_pReal , 163 1.0_pReal / 5529 6.0_pReal , &
. 0_pReal , . 225_pReal , - . 9_pReal , 2.5_pReal , 17 5.0_pReal / 51 2.0_pReal , &
. 0_pReal , . 0_pReal , 1.2_pReal , - 7 0.0_pReal / 2 7.0_pReal , 57 5.0_pReal / 1382 4.0_pReal , &
. 0_pReal , . 0_pReal , . 0_pReal , 3 5.0_pReal / 2 7.0_pReal , 4427 5.0_pReal / 11059 2.0_pReal , &
. 0_pReal , . 0_pReal , . 0_pReal , . 0_pReal , 25 3.0_pReal / 409 6.0_pReal ] , &
2014-08-26 20:14:32 +05:30
[ 5 , 5 ] , order = [ 2 , 1 ] ) !< coefficients in Butcher tableau (used for preliminary integration in stages 2 to 6)
2013-11-21 16:28:41 +05:30
real ( pReal ) , dimension ( 6 ) , parameter :: &
2014-08-26 20:14:32 +05:30
B = &
2013-11-21 16:28:41 +05:30
[ 3 7.0_pReal / 37 8.0_pReal , . 0_pReal , 25 0.0_pReal / 62 1.0_pReal , &
12 5.0_pReal / 59 4.0_pReal , . 0_pReal , 51 2.0_pReal / 177 1.0_pReal ] , & !< coefficients in Butcher tableau (used for final integration and error estimate)
DB = B - &
2014-05-27 20:16:03 +05:30
[ 282 5.0_pReal / 2764 8.0_pReal , . 0_pReal , 1857 5.0_pReal / 4838 4.0_pReal , &
1352 5.0_pReal / 5529 6.0_pReal , 27 7.0_pReal / 1433 6.0_pReal , 0.25_pReal ] !< coefficients in Butcher tableau (used for final integration and error estimate)
2013-11-21 16:28:41 +05:30
real ( pReal ) , dimension ( 5 ) , parameter :: &
C = [ 0.2_pReal , 0.3_pReal , 0.6_pReal , 1.0_pReal , 0.875_pReal ] !< coefficients in Butcher tableau (fractions of original time step in stages 2 to 6)
2013-04-29 16:47:30 +05:30
integer ( pInt ) :: &
e , & ! element index in element loop
i , & ! integration point index in ip loop
g , & ! grain index in grain loop
2014-09-03 01:41:57 +05:30
stage , & ! stage index in integration stage loop
2014-06-25 04:51:25 +05:30
s , & ! state index
2014-09-03 01:41:57 +05:30
n , &
2014-06-25 04:51:25 +05:30
p , &
cc , &
2014-09-03 01:16:52 +05:30
mySizePlasticDotState , & ! size of dot States
2014-06-25 04:51:25 +05:30
mySizeDamageDotState , &
mySizeThermalDotState
2013-11-21 16:28:41 +05:30
integer ( pInt ) , dimension ( 2 ) :: &
eIter ! bounds for element iteration
integer ( pInt ) , dimension ( 2 , mesh_NcpElems ) :: &
iIter , & ! bounds for ip iteration
gIter ! bounds for grain iteration
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
real ( pReal ) , dimension ( constitutive_maxSizeDotState , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
2014-09-03 01:16:52 +05:30
stateResiduum , & ! residuum from evolution in microstructure
2013-11-21 16:28:41 +05:30
relStateResiduum ! relative residuum from evolution in microstructure
2014-06-25 04:51:25 +05:30
real ( pReal ) , dimension ( constitutive_damage_maxSizeDotState , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
2014-09-03 01:16:52 +05:30
damageStateResiduum , & ! residuum from evolution in microstructure
2014-06-25 04:51:25 +05:30
relDamageStateResiduum ! relative residuum from evolution in microstructure
real ( pReal ) , dimension ( constitutive_thermal_maxSizeDotState , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
2014-09-03 01:16:52 +05:30
thermalStateResiduum , & ! residuum from evolution in microstructure
2014-06-25 04:51:25 +05:30
relThermalStateResiduum ! relative residuum from evolution in microstructure
2013-11-21 16:28:41 +05:30
logical :: &
singleRun ! flag indicating computation for single (g,i,e) triple
2014-08-26 20:14:32 +05:30
2013-04-26 18:53:36 +05:30
eIter = FEsolving_execElem ( 1 : 2 )
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2014-08-26 20:14:32 +05:30
write ( 6 , '(a,1x,i1)' ) '<< CRYST >> Runge--Kutta step' , 1
2014-05-27 20:16:03 +05:30
! --- LOOP ITERATOR FOR ELEMENT, GRAIN, IP ---
2013-04-26 18:53:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 )
iIter ( 1 : 2 , e ) = FEsolving_execIP ( 1 : 2 , e )
gIter ( 1 : 2 , e ) = [ 1_pInt , homogenization_Ngrains ( mesh_element ( 3 , e ) ) ]
enddo
2014-08-26 20:14:32 +05:30
2013-04-30 17:44:07 +05:30
singleRun = ( eIter ( 1 ) == eIter ( 2 ) . and . iIter ( 1 , eIter ( 1 ) ) == iIter ( 2 , eIter ( 2 ) ) )
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- FIRST RUNGE KUTTA STEP ---
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
crystallite_subdt ( g , i , e ) , crystallite_subFrac , g , i , e )
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,cc)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
2014-09-03 01:16:52 +05:30
cc = mappingConstitutive ( 1 , g , i , e )
p = mappingConstitutive ( 2 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , cc ) / = plasticState ( p ) % dotState ( : , cc ) ) . or . &
any ( damageState ( p ) % dotState ( : , cc ) / = damageState ( p ) % dotState ( : , cc ) ) . or . &
any ( thermalState ( p ) % dotState ( : , cc ) / = thermalState ( p ) % dotState ( : , cc ) ) ) then ! NaN occured in dotState
2014-05-27 20:16:03 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
else ! if broken local...
crystallite_todo ( g , i , e ) = . false . ! ... skip this one next time
endif
endif
2013-02-22 04:38:36 +05:30
endif
2011-03-29 12:57:19 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- SECOND TO SIXTH RUNGE KUTTA STEP ---
2014-05-27 20:16:03 +05:30
2014-09-03 01:41:57 +05:30
do stage = 1_pInt , 5_pInt
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- state update ---
2014-08-26 20:14:32 +05:30
!$OMP PARALLEL
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,cc)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
2014-06-25 04:51:25 +05:30
cc = mappingConstitutive ( 1 , g , i , e )
2014-09-03 01:41:57 +05:30
plasticState ( p ) % RKCK45dotState ( stage , : , cc ) = plasticState ( p ) % dotState ( : , cc ) ! store Runge-Kutta dotState
damageState ( p ) % RKCK45dotState ( stage , : , cc ) = damageState ( p ) % dotState ( : , cc ) ! store Runge-Kutta dotState
thermalState ( p ) % RKCK45dotState ( stage , : , cc ) = thermalState ( p ) % dotState ( : , cc ) ! store Runge-Kutta dotState
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-09-03 01:41:57 +05:30
!$OMP DO PRIVATE(p,cc,n)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
2014-06-25 04:51:25 +05:30
cc = mappingConstitutive ( 1 , g , i , e )
2014-07-02 17:57:39 +05:30
2014-09-03 01:41:57 +05:30
plasticState ( p ) % dotState ( : , cc ) = A ( 1 , stage ) * plasticState ( p ) % RKCK45dotState ( 1 , : , cc )
damageState ( p ) % dotState ( : , cc ) = A ( 1 , stage ) * damageState ( p ) % RKCK45dotState ( 1 , : , cc )
thermalState ( p ) % dotState ( : , cc ) = A ( 1 , stage ) * thermalState ( p ) % RKCK45dotState ( 1 , : , cc )
do n = 2_pInt , stage
plasticState ( p ) % dotState ( : , cc ) = &
plasticState ( p ) % dotState ( : , cc ) + A ( n , stage ) * plasticState ( p ) % RKCK45dotState ( n , : , cc )
damageState ( p ) % dotState ( : , cc ) = &
damageState ( p ) % dotState ( : , cc ) + A ( n , stage ) * damageState ( p ) % RKCK45dotState ( n , : , cc )
thermalState ( p ) % dotState ( : , cc ) = &
thermalState ( p ) % dotState ( : , cc ) + A ( n , stage ) * thermalState ( p ) % RKCK45dotState ( n , : , cc )
enddo
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-09-03 01:41:57 +05:30
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,cc)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
cc = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
plasticState ( p ) % state ( 1 : mySizePlasticDotState , cc ) = plasticState ( p ) % subState0 ( 1 : mySizePlasticDotState , cc ) &
+ plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , cc ) &
* crystallite_subdt ( g , i , e )
damageState ( p ) % state ( 1 : mySizeDamageDotState , cc ) = damageState ( p ) % subState0 ( 1 : mySizeDamageDotState , cc ) &
+ damageState ( p ) % dotState ( 1 : mySizeDamageDotState , cc ) &
* crystallite_subdt ( g , i , e )
thermalState ( p ) % state ( 1 : mySizeThermalDotState , cc ) = thermalState ( p ) % subState0 ( 1 : mySizeThermalDotState , cc ) &
+ thermalState ( p ) % dotState ( 1 : mySizeThermalDotState , cc ) &
* crystallite_subdt ( g , i , e )
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- state jump ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_stateJump ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- update dependent states ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-10-10 17:58:57 +05:30
call constitutive_microstructure ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-09-23 16:08:20 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2013-02-22 04:38:36 +05:30
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! update dependent state variables to be consistent with basic states
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- stress integration ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
2014-09-03 01:41:57 +05:30
crystallite_todo ( g , i , e ) = crystallite_integrateStress ( g , i , e , C ( stage ) ) ! fraction of original time step
2013-02-22 04:38:36 +05:30
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
2014-08-26 20:14:32 +05:30
!$OMP ENDDO
2013-02-22 04:38:36 +05:30
! --- dot state and RK dot state---
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2014-09-03 01:41:57 +05:30
write ( 6 , '(a,1x,i1)' ) '<< CRYST >> Runge--Kutta step' , stage + 1_pInt
2011-03-29 12:57:19 +05:30
#endif
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2014-09-03 01:41:57 +05:30
C ( stage ) * crystallite_subdt ( g , i , e ) , & ! fraction of original timestep
2013-02-22 04:38:36 +05:30
crystallite_subFrac , g , i , e )
enddo ; enddo ; enddo
!$OMP ENDDO
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,cc)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
2014-07-02 17:57:39 +05:30
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
cc = mappingConstitutive ( 1 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , cc ) / = plasticState ( p ) % dotState ( : , cc ) ) . or . &
any ( damageState ( p ) % dotState ( : , cc ) / = damageState ( p ) % dotState ( : , cc ) ) . or . &
any ( thermalState ( p ) % dotState ( : , cc ) / = thermalState ( p ) % dotState ( : , cc ) ) ) then ! NaN occured in dotState
2013-02-22 04:38:36 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
else ! if broken local...
crystallite_todo ( g , i , e ) = . false . ! ... skip this one next time
endif
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
enddo
2013-05-17 23:22:46 +05:30
!--------------------------------------------------------------------------------------------------
2014-06-25 04:51:25 +05:30
! --- STATE UPDATE WITH ERROR ESTIMATE FOR STATE ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
relStateResiduum = 0.0_pReal
2014-06-25 04:51:25 +05:30
relDamageStateResiduum = 0.0_pReal
relThermalStateResiduum = 0.0_pReal
2014-08-26 20:14:32 +05:30
!$OMP PARALLEL
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,cc)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
cc = mappingConstitutive ( 1 , g , i , e )
plasticState ( p ) % RKCK45dotState ( 6 , : , cc ) = plasticState ( p ) % dotState ( : , cc ) ! store Runge-Kutta dotState
damageState ( p ) % RKCK45dotState ( 6 , : , cc ) = damageState ( p ) % dotState ( : , cc ) ! store Runge-Kutta dotState
thermalState ( p ) % RKCK45dotState ( 6 , : , cc ) = thermalState ( p ) % dotState ( : , cc ) ! store Runge-Kutta dotState
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-09-03 01:16:52 +05:30
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,cc)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
cc = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
! --- absolute residuum in state ---
2014-08-26 20:14:32 +05:30
! NEED TO DO THE ADDITION IN THIS LENGTHY WAY BECAUSE OF PARALLELIZATION
2014-05-27 20:16:03 +05:30
! CAN'T USE A REDUCTION CLAUSE ON A POINTER OR USER DEFINED TYPE
2014-09-03 01:16:52 +05:30
stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) = &
( DB ( 1 ) * plasticState ( p ) % RKCK45dotState ( 1 , 1 : mySizePlasticDotState , cc ) &
+ DB ( 2 ) * plasticState ( p ) % RKCK45dotState ( 2 , 1 : mySizePlasticDotState , cc ) &
+ DB ( 3 ) * plasticState ( p ) % RKCK45dotState ( 3 , 1 : mySizePlasticDotState , cc ) &
+ DB ( 4 ) * plasticState ( p ) % RKCK45dotState ( 4 , 1 : mySizePlasticDotState , cc ) &
+ DB ( 5 ) * plasticState ( p ) % RKCK45dotState ( 5 , 1 : mySizePlasticDotState , cc ) &
+ DB ( 6 ) * plasticState ( p ) % RKCK45dotState ( 6 , 1 : mySizePlasticDotState , cc ) &
) * crystallite_subdt ( g , i , e )
damageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) = &
( DB ( 1 ) * damageState ( p ) % RKCK45dotState ( 1 , 1 : mySizeDamageDotState , cc ) &
+ DB ( 2 ) * damageState ( p ) % RKCK45dotState ( 2 , 1 : mySizeDamageDotState , cc ) &
+ DB ( 3 ) * damageState ( p ) % RKCK45dotState ( 3 , 1 : mySizeDamageDotState , cc ) &
+ DB ( 4 ) * damageState ( p ) % RKCK45dotState ( 4 , 1 : mySizeDamageDotState , cc ) &
+ DB ( 5 ) * damageState ( p ) % RKCK45dotState ( 5 , 1 : mySizeDamageDotState , cc ) &
+ DB ( 6 ) * damageState ( p ) % RKCK45dotState ( 6 , 1 : mySizeDamageDotState , cc ) &
) * crystallite_subdt ( g , i , e )
thermalStateResiduum ( 1 : mySizethermalDotState , g , i , e ) = &
( DB ( 1 ) * thermalState ( p ) % RKCK45dotState ( 1 , 1 : mySizeThermalDotState , cc ) &
+ DB ( 2 ) * thermalState ( p ) % RKCK45dotState ( 2 , 1 : mySizeThermalDotState , cc ) &
+ DB ( 3 ) * thermalState ( p ) % RKCK45dotState ( 3 , 1 : mySizeThermalDotState , cc ) &
+ DB ( 4 ) * thermalState ( p ) % RKCK45dotState ( 4 , 1 : mySizeThermalDotState , cc ) &
+ DB ( 5 ) * thermalState ( p ) % RKCK45dotState ( 5 , 1 : mySizeThermalDotState , cc ) &
+ DB ( 6 ) * thermalState ( p ) % RKCK45dotState ( 6 , 1 : mySizeThermalDotState , cc ) &
) * crystallite_subdt ( g , i , e )
2014-05-27 20:16:03 +05:30
! --- dot state ---
2014-08-26 20:14:32 +05:30
2014-06-25 04:51:25 +05:30
plasticState ( p ) % dotState ( : , cc ) = B ( 1 ) * plasticState ( p ) % RKCK45dotState ( 1 , : , cc ) &
2014-09-03 01:16:52 +05:30
+ B ( 2 ) * plasticState ( p ) % RKCK45dotState ( 2 , : , cc ) &
+ B ( 3 ) * plasticState ( p ) % RKCK45dotState ( 3 , : , cc ) &
+ B ( 4 ) * plasticState ( p ) % RKCK45dotState ( 4 , : , cc ) &
+ B ( 5 ) * plasticState ( p ) % RKCK45dotState ( 5 , : , cc ) &
+ B ( 6 ) * plasticState ( p ) % RKCK45dotState ( 6 , : , cc )
damageState ( p ) % dotState ( : , cc ) = B ( 1 ) * damageState ( p ) % RKCK45dotState ( 1 , : , cc ) &
+ B ( 2 ) * damageState ( p ) % RKCK45dotState ( 2 , : , cc ) &
+ B ( 3 ) * damageState ( p ) % RKCK45dotState ( 3 , : , cc ) &
+ B ( 4 ) * damageState ( p ) % RKCK45dotState ( 4 , : , cc ) &
+ B ( 5 ) * damageState ( p ) % RKCK45dotState ( 5 , : , cc ) &
+ B ( 6 ) * damageState ( p ) % RKCK45dotState ( 6 , : , cc )
2014-06-25 04:51:25 +05:30
thermalState ( p ) % dotState ( : , cc ) = B ( 1 ) * thermalState ( p ) % RKCK45dotState ( 1 , : , cc ) &
2014-09-03 01:16:52 +05:30
+ B ( 2 ) * thermalState ( p ) % RKCK45dotState ( 2 , : , cc ) &
+ B ( 3 ) * thermalState ( p ) % RKCK45dotState ( 3 , : , cc ) &
+ B ( 4 ) * thermalState ( p ) % RKCK45dotState ( 4 , : , cc ) &
+ B ( 5 ) * thermalState ( p ) % RKCK45dotState ( 5 , : , cc ) &
+ B ( 6 ) * thermalState ( p ) % RKCK45dotState ( 6 , : , cc )
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-09-03 01:16:52 +05:30
! --- state and update ---
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,cc)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-07-02 17:57:39 +05:30
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
cc = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
plasticState ( p ) % state ( 1 : mySizePlasticDotState , cc ) = plasticState ( p ) % subState0 ( 1 : mySizePlasticDotState , cc ) &
2014-09-03 01:16:52 +05:30
+ plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , cc ) &
* crystallite_subdt ( g , i , e )
2014-06-25 04:51:25 +05:30
damageState ( p ) % state ( 1 : mySizeDamageDotState , cc ) = damageState ( p ) % subState0 ( 1 : mySizeDamageDotState , cc ) &
2014-09-03 01:16:52 +05:30
+ damageState ( p ) % dotState ( 1 : mySizeDamageDotState , cc ) &
* crystallite_subdt ( g , i , e )
2014-06-25 04:51:25 +05:30
thermalState ( p ) % state ( 1 : mySizeThermalDotState , cc ) = thermalState ( p ) % subState0 ( 1 : mySizeThermalDotState , cc ) &
2014-09-03 01:16:52 +05:30
+ thermalState ( p ) % dotState ( 1 : mySizeThermalDotState , cc ) &
* crystallite_subdt ( g , i , e )
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-09-03 01:16:52 +05:30
! --- relative residui and state convergence ---
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,cc,s)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
cc = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
forall ( s = 1_pInt : mySizePlasticDotState , abs ( plasticState ( p ) % state ( s , cc ) ) > 0.0_pReal ) &
relStateResiduum ( s , g , i , e ) = stateResiduum ( s , g , i , e ) / plasticState ( p ) % state ( s , cc )
2014-09-03 01:16:52 +05:30
forall ( s = 1_pInt : mySizeDamageDotState , abs ( damageState ( p ) % state ( s , cc ) ) > 0.0_pReal ) &
2014-06-25 04:51:25 +05:30
relDamageStateResiduum ( s , g , i , e ) = damageStateResiduum ( s , g , i , e ) / damageState ( p ) % state ( s , cc )
forall ( s = 1_pInt : mySizeThermalDotState , abs ( thermalState ( p ) % state ( s , cc ) ) > 0.0_pReal ) &
relThermalStateResiduum ( s , g , i , e ) = thermalStateResiduum ( s , g , i , e ) / thermalState ( p ) % state ( s , cc )
2014-05-27 20:16:03 +05:30
!$OMP FLUSH(relStateResiduum)
2014-09-03 01:16:52 +05:30
!$OMP FLUSH(relDamageStateResiduum)
!$OMP FLUSH(relThermalStateResiduum)
! @Martin: do we need flushing? why..?
2014-05-27 20:16:03 +05:30
crystallite_todo ( g , i , e ) = &
2014-06-25 04:51:25 +05:30
( all ( abs ( relStateResiduum ( 1 : mySizePlasticDotState , g , i , e ) ) < &
rTol_crystalliteState . or . &
abs ( stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) ) < &
plasticState ( p ) % aTolState ( 1 : mySizePlasticDotState ) ) &
. and . all ( abs ( relDamageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) ) < &
rTol_crystalliteState . or . &
abs ( damageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) ) < &
damageState ( p ) % aTolState ( 1 : mySizeDamageDotState ) ) &
. and . all ( abs ( relThermalStateResiduum ( 1 : mySizeThermalDotState , g , i , e ) ) < &
rTol_crystalliteState . or . &
abs ( thermalStateResiduum ( 1 : mySizeThermalDotState , g , i , e ) ) < &
thermalState ( p ) % aTolState ( 1 : mySizeThermalDotState ) ) )
2014-07-02 17:57:39 +05:30
#ifndef _OPENMP
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
write ( 6 , '(a,i8,1x,i3,1x,i3,/)' ) '<< CRYST >> updateState at el ip g ' , e , i , g
write ( 6 , '(a,/,(12x,12(f12.1,1x)),/)' ) '<< CRYST >> absolute residuum tolerance' , &
2014-09-03 01:16:52 +05:30
stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) / plasticState ( p ) % aTolState ( 1 : mySizePlasticDotState )
2014-07-02 17:57:39 +05:30
write ( 6 , '(a,/,(12x,12(f12.1,1x)),/)' ) '<< CRYST >> relative residuum tolerance' , &
2014-09-03 01:16:52 +05:30
relStateResiduum ( 1 : mySizePlasticDotState , g , i , e ) / rTol_crystalliteState
2014-07-02 17:57:39 +05:30
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> dotState' , &
plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , cc )
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> new state' , &
plasticState ( p ) % state ( 1 : mySizePlasticDotState , cc )
endif
2011-03-29 12:57:19 +05:30
#endif
2013-02-22 04:38:36 +05:30
endif
2011-11-04 18:14:50 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- STATE JUMP ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_stateJump ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
2011-11-04 18:14:50 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-05-17 23:22:46 +05:30
!--------------------------------------------------------------------------------------------------
! --- UPDATE DEPENDENT STATES IF RESIDUUM BELOW TOLERANCE ---
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-10-10 17:58:57 +05:30
call constitutive_microstructure ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-09-23 16:08:20 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2014-09-03 01:16:52 +05:30
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! update dependent state variables to be consistent with basic states
2010-10-01 17:48:49 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-05-17 23:22:46 +05:30
!--------------------------------------------------------------------------------------------------
! --- FINAL STRESS INTEGRATION STEP IF RESIDUUM BELOW TOLERANCE ---
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_integrateStress ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-05-17 23:22:46 +05:30
!--------------------------------------------------------------------------------------------------
! --- SET CONVERGENCE FLAG ---
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-06-11 22:02:09 +05:30
crystallite_converged ( g , i , e ) = . true . ! if still "to do" then converged per definition
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
!$OMP CRITICAL (distributionState)
debug_StateLoopDistribution ( 6 , numerics_integrationMode ) = &
debug_StateLoopDistribution ( 6 , numerics_integrationMode ) + 1_pInt
!$OMP END CRITICAL (distributionState)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- nonlocal convergence check ---
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2014-09-03 01:16:52 +05:30
write ( 6 , '(a,i8,a,i2,/)' ) '<< CRYST >> ' , count ( crystallite_converged ( : , : , : ) ) , ' grains converged' ! if not requesting Integration of just a single IP
2014-05-27 20:16:03 +05:30
if ( ( . not . singleRun ) . and . any ( . not . crystallite_converged . and . . not . crystallite_localPlasticity ) ) & ! any non-local not yet converged (or broken)...
2014-09-03 01:16:52 +05:30
crystallite_converged = crystallite_converged . and . crystallite_localPlasticity ! ...restart all non-local as not converged
2013-02-22 04:38:36 +05:30
end subroutine crystallite_integrateStateRKCK45
2010-10-01 17:48:49 +05:30
2012-05-17 20:55:21 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-10-16 18:34:59 +05:30
!> @brief integrate stress, state with 1st order Euler method with adaptive step size
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-04-26 18:53:36 +05:30
subroutine crystallite_integrateStateAdaptiveEuler ( )
2014-05-27 20:16:03 +05:30
2013-11-21 16:28:41 +05:30
use debug , only : &
debug_level , &
debug_crystallite , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_e , &
debug_i , &
debug_g , &
debug_StateLoopDistribution
use numerics , only : &
rTol_crystalliteState , &
numerics_integrationMode
2014-08-26 20:14:32 +05:30
use FEsolving , only : &
FEsolving_execElem , &
2013-11-21 16:28:41 +05:30
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_Ngrains , &
2014-05-27 20:16:03 +05:30
plasticState , &
2014-06-25 04:51:25 +05:30
damageState , &
thermalState , &
2014-06-23 00:28:29 +05:30
mappingConstitutive , &
2013-11-21 16:28:41 +05:30
homogenization_maxNgrains
use constitutive , only : &
2014-05-27 20:16:03 +05:30
constitutive_collectDotState , &
constitutive_microstructure , &
2014-09-23 16:08:20 +05:30
constitutive_maxSizeDotState , &
constitutive_damage_maxSizeDotState , &
2014-06-25 04:51:25 +05:30
constitutive_thermal_maxSizeDotState
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
implicit none
2013-11-21 16:28:41 +05:30
integer ( pInt ) :: &
e , & ! element index in element loop
i , & ! integration point index in ip loop
g , & ! grain index in grain loop
2014-06-25 04:51:25 +05:30
s , & ! state index
p , &
c , &
2014-09-03 01:16:52 +05:30
mySizePlasticDotState , & ! size of dot states
2014-06-25 04:51:25 +05:30
mySizeDamageDotState , &
mySizeThermalDotState
2013-11-21 16:28:41 +05:30
integer ( pInt ) , dimension ( 2 ) :: &
eIter ! bounds for element iteration
integer ( pInt ) , dimension ( 2 , mesh_NcpElems ) :: &
iIter , & ! bounds for ip iteration
gIter ! bounds for grain iteration
2013-02-22 04:38:36 +05:30
real ( pReal ) , dimension ( constitutive_maxSizeDotState , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
2013-11-21 16:28:41 +05:30
stateResiduum , & ! residuum from evolution in micrstructure
relStateResiduum ! relative residuum from evolution in microstructure
2014-06-25 04:51:25 +05:30
real ( pReal ) , dimension ( constitutive_damage_maxSizeDotState , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
damageStateResiduum , & ! residuum from evolution in micrstructure
relDamageStateResiduum ! relative residuum from evolution in microstructure
real ( pReal ) , dimension ( constitutive_thermal_maxSizeDotState , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) :: &
thermalStateResiduum , & ! residuum from evolution in micrstructure
relThermalStateResiduum ! relative residuum from evolution in microstructure
2014-05-27 20:16:03 +05:30
2013-11-21 16:28:41 +05:30
logical :: &
singleRun ! flag indicating computation for single (g,i,e) triple
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- LOOP ITERATOR FOR ELEMENT, GRAIN, IP ---
2013-04-26 18:53:36 +05:30
eIter = FEsolving_execElem ( 1 : 2 )
do e = eIter ( 1 ) , eIter ( 2 )
iIter ( 1 : 2 , e ) = FEsolving_execIP ( 1 : 2 , e )
gIter ( 1 : 2 , e ) = [ 1_pInt , homogenization_Ngrains ( mesh_element ( 3 , e ) ) ]
enddo
2014-08-26 20:14:32 +05:30
2013-04-30 17:44:07 +05:30
singleRun = ( eIter ( 1 ) == eIter ( 2 ) . and . iIter ( 1 , eIter ( 1 ) ) == iIter ( 2 , eIter ( 2 ) ) )
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
stateResiduum = 0.0_pReal
relStateResiduum = 0.0_pReal
2014-06-25 04:51:25 +05:30
damageStateResiduum = 0.0_pReal
relDamageStateResiduum = 0.0_pReal
thermalStateResiduum = 0.0_pReal
relThermalStateResiduum = 0.0_pReal
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
integrationMode : if ( numerics_integrationMode == 1_pInt ) then
2014-08-26 20:14:32 +05:30
!$OMP PARALLEL
2013-10-16 18:34:59 +05:30
! --- DOT STATE (EULER INTEGRATION) ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
crystallite_subdt ( g , i , e ) , crystallite_subFrac , g , i , e )
2012-05-17 20:55:21 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
2014-05-27 20:16:03 +05:30
if ( crystallite_todo ( g , i , e ) ) then
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , c ) / = plasticState ( p ) % dotState ( : , c ) ) . or . &
any ( damageState ( p ) % dotState ( : , c ) / = damageState ( p ) % dotState ( : , c ) ) . or . &
any ( thermalState ( p ) % dotState ( : , c ) / = thermalState ( p ) % dotState ( : , c ) ) ) then ! NaN occured in dotState
2014-05-27 20:16:03 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
else ! if broken local...
crystallite_todo ( g , i , e ) = . false . ! ... skip this one next time
endif
endif
2013-02-22 04:38:36 +05:30
endif
2014-05-27 20:16:03 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- STATE UPDATE (EULER INTEGRATION) ---
2014-09-03 01:16:52 +05:30
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) = - 0.5_pReal &
* plasticState ( p ) % dotstate ( 1 : mySizePlasticDotState , c ) &
2014-08-26 20:14:32 +05:30
* crystallite_subdt ( g , i , e ) ! contribution to absolute residuum in state
2014-06-25 04:51:25 +05:30
damageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) = - 0.5_pReal &
* damageState ( p ) % dotstate ( 1 : mySizeDamageDotState , c ) &
2014-08-26 20:14:32 +05:30
* crystallite_subdt ( g , i , e ) ! contribution to absolute residuum in state
2014-06-25 04:51:25 +05:30
thermalStateResiduum ( 1 : mySizeThermalDotState , g , i , e ) = - 0.5_pReal &
* thermalState ( p ) % dotstate ( 1 : mySizeThermalDotState , c ) &
2014-08-26 20:14:32 +05:30
* crystallite_subdt ( g , i , e ) ! contribution to absolute residuum in state
2014-06-25 04:51:25 +05:30
plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) = plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) &
+ plasticState ( p ) % dotstate ( 1 : mySizePlasticDotState , c ) &
2014-08-26 20:14:32 +05:30
* crystallite_subdt ( g , i , e )
2014-06-25 04:51:25 +05:30
damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) = damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) &
+ damageState ( p ) % dotstate ( 1 : mySizeDamageDotState , c ) &
2014-08-26 20:14:32 +05:30
* crystallite_subdt ( g , i , e )
2014-06-25 04:51:25 +05:30
thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) = thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) &
+ thermalState ( p ) % dotstate ( 1 : mySizeThermalDotState , c ) &
2014-08-26 20:14:32 +05:30
* crystallite_subdt ( g , i , e )
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
2014-08-26 20:14:32 +05:30
!$OMP ENDDO
2013-02-22 04:38:36 +05:30
! --- STATE JUMP ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_stateJump ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- UPDATE DEPENDENT STATES (EULER INTEGRATION) ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
2013-11-21 16:28:41 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2013-10-19 00:27:28 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-10-10 17:58:57 +05:30
call constitutive_microstructure ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-09-23 16:08:20 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2013-11-21 16:28:41 +05:30
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! update dependent state variables to be consistent with basic states
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
!$OMP END PARALLEL
2014-05-27 20:16:03 +05:30
endif integrationMode
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- STRESS INTEGRATION (EULER INTEGRATION) ---
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL DO
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_integrateStress ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
2014-05-27 20:16:03 +05:30
!$OMP END PARALLEL DO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
if ( numerics_integrationMode == 1_pInt ) then
2014-08-26 20:14:32 +05:30
!$OMP PARALLEL
2013-10-16 18:34:59 +05:30
! --- DOT STATE (HEUN METHOD) ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2013-10-19 00:27:28 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
crystallite_subdt ( g , i , e ) , crystallite_subFrac , g , i , e )
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
if ( any ( plasticState ( p ) % dotState ( : , c ) / = plasticState ( p ) % dotState ( : , c ) ) . or . &
2014-09-03 01:16:52 +05:30
any ( damageState ( p ) % dotState ( : , c ) / = damageState ( p ) % dotState ( : , c ) ) . or . &
2014-06-25 04:51:25 +05:30
any ( thermalState ( p ) % dotState ( : , c ) / = thermalState ( p ) % dotState ( : , c ) ) ) then ! NaN occured in dotState
2014-05-27 20:16:03 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
else ! if broken local...
crystallite_todo ( g , i , e ) = . false . ! ... skip this one next time
endif
endif
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-10-16 18:34:59 +05:30
! --- ERROR ESTIMATE FOR STATE (HEUN METHOD) ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP SINGLE
relStateResiduum = 0.0_pReal
2014-06-25 04:51:25 +05:30
relDamageStateResiduum = 0.0_pReal
relThermalStateResiduum = 0.0_pReal
2013-02-22 04:38:36 +05:30
!$OMP END SINGLE
2014-05-27 20:16:03 +05:30
2014-09-03 01:16:52 +05:30
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,c,s)
2014-05-27 20:16:03 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2013-02-22 04:38:36 +05:30
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
mySizeDamageDotState = damageState ( p ) % sizeDotState
mySizeThermalDotState = thermalState ( p ) % sizeDotState
2014-05-27 20:16:03 +05:30
! --- contribution of heun step to absolute residui ---
2014-08-26 20:14:32 +05:30
2014-06-25 04:51:25 +05:30
stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) = stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) &
+ 0.5_pReal * plasticState ( p ) % dotState ( : , c ) &
2014-07-02 17:57:39 +05:30
* crystallite_subdt ( g , i , e ) ! contribution to absolute residuum in state
2014-06-25 04:51:25 +05:30
damageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) = damageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) &
+ 0.5_pReal * damageState ( p ) % dotState ( : , c ) &
2014-07-02 17:57:39 +05:30
* crystallite_subdt ( g , i , e ) ! contribution to absolute residuum in state
2014-06-25 04:51:25 +05:30
thermalStateResiduum ( 1 : mySizeThermalDotState , g , i , e ) = thermalStateResiduum ( 1 : mySizeThermalDotState , g , i , e ) &
+ 0.5_pReal * thermalState ( p ) % dotState ( : , c ) &
2014-07-02 17:57:39 +05:30
* crystallite_subdt ( g , i , e ) ! contribution to absolute residuum in state
2014-05-27 20:16:03 +05:30
2013-10-16 18:34:59 +05:30
!$OMP FLUSH(stateResiduum)
2014-09-03 01:16:52 +05:30
!$OMP FLUSH(damageStateResiduum)
!$OMP FLUSH(thermalStateResiduum)
! --- relative residui ---
2014-06-25 04:51:25 +05:30
forall ( s = 1_pInt : mySizePlasticDotState , abs ( plasticState ( p ) % dotState ( s , c ) ) > 0.0_pReal ) &
relStateResiduum ( s , g , i , e ) = stateResiduum ( s , g , i , e ) / plasticState ( p ) % dotState ( s , c )
forall ( s = 1_pInt : mySizeDamageDotState , abs ( damageState ( p ) % dotState ( s , c ) ) > 0.0_pReal ) &
relDamageStateResiduum ( s , g , i , e ) = damageStateResiduum ( s , g , i , e ) / damageState ( p ) % dotState ( s , c )
forall ( s = 1_pInt : mySizeThermalDotState , abs ( thermalState ( p ) % dotState ( s , c ) ) > 0.0_pReal ) &
relThermalStateResiduum ( s , g , i , e ) = thermalStateResiduum ( s , g , i , e ) / thermalState ( p ) % dotState ( s , c )
2013-10-16 18:34:59 +05:30
!$OMP FLUSH(relStateResiduum)
2014-09-03 01:16:52 +05:30
!$OMP FLUSH(relDamageStateResiduum)
!$OMP FLUSH(relthermalStateResiduum)
#ifndef _OPENMP
2014-07-02 17:57:39 +05:30
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
write ( 6 , '(a,i8,1x,i2,1x,i3,/)' ) '<< CRYST >> updateState at el ip g ' , e , i , g
write ( 6 , '(a,/,(12x,12(f12.1,1x)),/)' ) '<< CRYST >> absolute residuum tolerance' , &
2014-06-25 04:51:25 +05:30
stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) / plasticState ( p ) % aTolState ( 1 : mySizePlasticDotState )
2014-05-27 20:16:03 +05:30
write ( 6 , '(a,/,(12x,12(f12.1,1x)),/)' ) '<< CRYST >> relative residuum tolerance' , &
2014-06-25 04:51:25 +05:30
relStateResiduum ( 1 : mySizePlasticDotState , g , i , e ) / rTol_crystalliteState
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> dotState' , plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , c ) &
- 2.0_pReal * stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) / crystallite_subdt ( g , i , e ) ! calculate former dotstate from higher order solution and state residuum
2014-09-03 01:41:57 +05:30
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> new state' , plasticState ( p ) % state ( 1 : mySizePlasticDotState , c )
2014-05-27 20:16:03 +05:30
endif
2012-03-09 01:55:28 +05:30
#endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- converged ? ---
2014-06-25 04:51:25 +05:30
if ( all ( abs ( relStateResiduum ( 1 : mySizePlasticDotState , g , i , e ) ) < &
rTol_crystalliteState . or . &
abs ( stateResiduum ( 1 : mySizePlasticDotState , g , i , e ) ) < &
plasticState ( p ) % aTolState ( 1 : mySizePlasticDotState ) ) &
. and . all ( abs ( relDamageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) ) < &
rTol_crystalliteState . or . &
abs ( damageStateResiduum ( 1 : mySizeDamageDotState , g , i , e ) ) < &
damageState ( p ) % aTolState ( 1 : mySizeDamageDotState ) ) &
. and . all ( abs ( relThermalStateResiduum ( 1 : mySizeThermalDotState , g , i , e ) ) < &
rTol_crystalliteState . or . &
abs ( thermalStateResiduum ( 1 : mySizeThermalDotState , g , i , e ) ) < &
thermalState ( p ) % aTolState ( 1 : mySizeThermalDotState ) ) ) then
2014-05-27 20:16:03 +05:30
crystallite_converged ( g , i , e ) = . true . ! ... converged per definitionem
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
!$OMP CRITICAL (distributionState)
debug_StateLoopDistribution ( 2 , numerics_integrationMode ) = &
debug_StateLoopDistribution ( 2 , numerics_integrationMode ) + 1_pInt
!$OMP END CRITICAL (distributionState)
endif
endif
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
elseif ( numerics_integrationMode > 1 ) then ! stiffness calculation
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL DO
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
crystallite_converged ( g , i , e ) = . true . ! ... converged per definitionem
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
!$OMP CRITICAL (distributionState)
debug_StateLoopDistribution ( 2 , numerics_integrationMode ) = &
debug_StateLoopDistribution ( 2 , numerics_integrationMode ) + 1_pInt
!$OMP END CRITICAL (distributionState)
endif
endif
enddo ; enddo ; enddo
2014-05-27 20:16:03 +05:30
!$OMP END PARALLEL DO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- NONLOCAL CONVERGENCE CHECK ---
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i8,a,i2,/)' ) '<< CRYST >> ' , count ( crystallite_converged ( : , : , : ) ) , ' grains converged'
2014-05-27 20:16:03 +05:30
if ( ( . not . singleRun ) . and . any ( . not . crystallite_converged . and . . not . crystallite_localPlasticity ) ) & ! any non-local not yet converged (or broken)...
2014-08-27 21:24:11 +05:30
crystallite_converged = crystallite_converged . and . crystallite_localPlasticity ! ...restart all non-local as not converged
2014-05-27 20:16:03 +05:30
2012-03-09 01:55:28 +05:30
end subroutine crystallite_integrateStateAdaptiveEuler
2010-10-01 17:48:49 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-10-16 18:34:59 +05:30
!> @brief integrate stress, and state with 1st order explicit Euler method
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-04-26 18:53:36 +05:30
subroutine crystallite_integrateStateEuler ( )
2013-11-21 16:28:41 +05:30
use debug , only : &
debug_level , &
debug_crystallite , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_e , &
debug_i , &
debug_g , &
debug_StateLoopDistribution
use numerics , only : &
numerics_integrationMode , &
numerics_timeSyncing
2014-08-26 20:14:32 +05:30
use FEsolving , only : &
FEsolving_execElem , &
2013-11-21 16:28:41 +05:30
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems
use material , only : &
2014-05-27 20:16:03 +05:30
plasticState , &
2014-06-25 04:51:25 +05:30
damageState , &
thermalState , &
2014-06-23 00:28:29 +05:30
mappingConstitutive , &
2013-11-21 16:28:41 +05:30
homogenization_Ngrains
use constitutive , only : &
2014-05-27 20:16:03 +05:30
constitutive_collectDotState , &
2014-06-23 00:28:29 +05:30
constitutive_microstructure
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
implicit none
2013-11-21 16:28:41 +05:30
integer ( pInt ) :: &
e , & ! element index in element loop
i , & ! integration point index in ip loop
g , & ! grain index in grain loop
2014-06-25 04:51:25 +05:30
p , & ! phase loop
c , &
mySizePlasticDotState , &
mySizeDamageDotState , &
mySizeThermalDotState
2013-11-21 16:28:41 +05:30
integer ( pInt ) , dimension ( 2 ) :: &
eIter ! bounds for element iteration
integer ( pInt ) , dimension ( 2 , mesh_NcpElems ) :: &
iIter , & ! bounds for ip iteration
gIter ! bounds for grain iteration
logical :: &
singleRun ! flag indicating computation for single (g,i,e) triple
2013-04-26 18:53:36 +05:30
eIter = FEsolving_execElem ( 1 : 2 )
do e = eIter ( 1 ) , eIter ( 2 )
iIter ( 1 : 2 , e ) = FEsolving_execIP ( 1 : 2 , e )
gIter ( 1 : 2 , e ) = [ 1_pInt , homogenization_Ngrains ( mesh_element ( 3 , e ) ) ]
enddo
2014-08-26 20:14:32 +05:30
2013-04-30 17:44:07 +05:30
singleRun = ( eIter ( 1 ) == eIter ( 2 ) . and . iIter ( 1 , eIter ( 1 ) ) == iIter ( 2 , eIter ( 2 ) ) )
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
if ( numerics_integrationMode == 1_pInt ) then
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL
2014-08-26 20:14:32 +05:30
2013-10-16 18:34:59 +05:30
! --- DOT STATE ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2013-10-19 00:27:28 +05:30
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
crystallite_subdt ( g , i , e ) , crystallite_subFrac , g , i , e )
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
2014-09-03 01:16:52 +05:30
c = mappingConstitutive ( 1 , g , i , e )
p = mappingConstitutive ( 2 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , c ) / = plasticState ( p ) % dotState ( : , c ) ) . or . &
any ( damageState ( p ) % dotState ( : , c ) / = damageState ( p ) % dotState ( : , c ) ) . or . &
any ( thermalState ( p ) % dotState ( : , c ) / = thermalState ( p ) % dotState ( : , c ) ) ) then ! NaN occured in dotState
2014-05-27 20:16:03 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) . and . . not . numerics_timeSyncing ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
else ! if broken local...
crystallite_todo ( g , i , e ) = . false . ! ... skip this one next time
endif
endif
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-10-16 18:34:59 +05:30
! --- UPDATE STATE ---
2014-09-03 01:16:52 +05:30
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) = plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) &
+ plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , c ) &
2014-06-25 04:51:25 +05:30
* crystallite_subdt ( g , i , e )
2014-09-03 01:16:52 +05:30
damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) = damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) &
+ damageState ( p ) % dotState ( 1 : mySizeDamageDotState , c ) &
2014-06-25 04:51:25 +05:30
* crystallite_subdt ( g , i , e )
2014-09-03 01:16:52 +05:30
thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) = thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) &
+ thermalState ( p ) % dotState ( 1 : mySizeThermalDotState , c ) &
2014-06-25 04:51:25 +05:30
* crystallite_subdt ( g , i , e )
2014-08-26 20:14:32 +05:30
2014-07-02 17:57:39 +05:30
#ifndef _OPENMP
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-07-02 17:57:39 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i3,/)' ) '<< CRYST >> update state at el ip g ' , e , i , g
2014-07-23 18:56:05 +05:30
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> dotState' , plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , c )
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> new state' , plasticState ( p ) % state ( 1 : mySizePlasticDotState , c )
2014-07-02 17:57:39 +05:30
endif
#endif
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- STATE JUMP ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_stateJump ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) & ! if broken non-local...
. and . . not . numerics_timeSyncing ) then
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- UPDATE DEPENDENT STATES ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2013-10-19 00:27:28 +05:30
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) &
2014-10-10 17:58:57 +05:30
call constitutive_microstructure ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-09-23 16:08:20 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2013-02-22 04:38:36 +05:30
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! update dependent state variables to be consistent with basic states
2014-06-25 04:51:25 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
!$OMP END PARALLEL
2013-02-22 04:38:36 +05:30
endif
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
!$OMP PARALLEL
2013-02-22 04:38:36 +05:30
! --- STRESS INTEGRATION ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_integrateStress ( g , i , e )
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) & ! if broken non-local...
. and . . not . numerics_timeSyncing ) then
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
2011-11-04 18:14:50 +05:30
enddo ; enddo ; enddo
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- SET CONVERGENCE FLAG ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
crystallite_converged ( g , i , e ) = . true . ! if still "to do" then converged per definitionem
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
!$OMP CRITICAL (distributionState)
debug_StateLoopDistribution ( 1 , numerics_integrationMode ) = &
debug_StateLoopDistribution ( 1 , numerics_integrationMode ) + 1_pInt
!$OMP END CRITICAL (distributionState)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- CHECK NON-LOCAL CONVERGENCE ---
2014-08-26 20:14:32 +05:30
if ( . not . singleRun ) then ! if not requesting Integration of just a single IP
2013-02-22 04:38:36 +05:30
if ( any ( . not . crystallite_converged . and . . not . crystallite_localPlasticity ) & ! any non-local not yet converged (or broken)...
2013-10-19 00:27:28 +05:30
. and . . not . numerics_timeSyncing ) &
2013-02-22 04:38:36 +05:30
crystallite_converged = crystallite_converged . and . crystallite_localPlasticity ! ...restart all non-local as not converged
endif
2014-08-26 20:14:32 +05:30
2012-03-09 01:55:28 +05:30
end subroutine crystallite_integrateStateEuler
2010-10-01 17:48:49 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2014-08-26 20:14:32 +05:30
!> @brief integrate stress, state with adaptive 1st order explicit Euler method
!> using Fixed Point Iteration to adapt the stepsize
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-04-26 18:53:36 +05:30
subroutine crystallite_integrateStateFPI ( )
2013-11-21 16:28:41 +05:30
use debug , only : &
debug_e , &
debug_i , &
debug_g , &
debug_level , &
debug_crystallite , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_StateLoopDistribution
use numerics , only : &
nState , &
numerics_integrationMode , &
rTol_crystalliteState
use FEsolving , only : &
2014-08-26 20:14:32 +05:30
FEsolving_execElem , &
2013-11-21 16:28:41 +05:30
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems
use material , only : &
2014-05-27 20:16:03 +05:30
plasticState , &
2014-06-25 04:51:25 +05:30
damageState , &
thermalState , &
2014-06-23 00:28:29 +05:30
mappingConstitutive , &
2013-11-21 16:28:41 +05:30
homogenization_Ngrains
use constitutive , only : &
2014-05-27 20:16:03 +05:30
constitutive_collectDotState , &
constitutive_microstructure , &
2014-09-23 16:08:20 +05:30
constitutive_maxSizeDotState , &
constitutive_damage_maxSizeDotState , &
2014-06-25 04:51:25 +05:30
constitutive_thermal_maxSizeDotState
2014-07-02 17:57:39 +05:30
2014-08-26 20:14:32 +05:30
implicit none
2013-05-17 23:22:46 +05:30
integer ( pInt ) :: &
NiterationState , & !< number of iterations in state loop
e , & !< element index in element loop
i , & !< integration point index in ip loop
g , & !< grain index in grain loop
2014-06-25 04:51:25 +05:30
p , &
c , &
2014-09-03 01:16:52 +05:30
mySizePlasticDotState , & ! size of dot states
2014-06-25 04:51:25 +05:30
mySizeDamageDotState , &
2014-09-23 02:04:42 +05:30
mySizeThermalDotState
2013-11-21 16:28:41 +05:30
integer ( pInt ) , dimension ( 2 ) :: &
eIter ! bounds for element iteration
integer ( pInt ) , dimension ( 2 , mesh_NcpElems ) :: &
iIter , & ! bounds for ip iteration
gIter ! bounds for grain iteration
real ( pReal ) :: &
dot_prod12 , &
dot_prod22 , &
2014-06-25 04:51:25 +05:30
stateDamper , & ! damper for integration of state
damageStateDamper , &
thermalStateDamper
real ( pReal ) , dimension ( constitutive_maxSizeDotState ) :: &
2013-11-21 16:28:41 +05:30
stateResiduum , &
tempState
2014-06-25 04:51:25 +05:30
real ( pReal ) , dimension ( constitutive_damage_maxSizeDotState ) :: &
damageStateResiduum , & ! residuum from evolution in micrstructure
2014-08-26 20:14:32 +05:30
tempDamageState
2014-06-25 04:51:25 +05:30
real ( pReal ) , dimension ( constitutive_thermal_maxSizeDotState ) :: &
thermalStateResiduum , & ! residuum from evolution in micrstructure
2014-08-26 20:14:32 +05:30
tempThermalState
2013-11-21 16:28:41 +05:30
logical :: &
2014-01-22 00:15:41 +05:30
singleRun , & ! flag indicating computation for single (g,i,e) triple
doneWithIntegration
2014-08-26 20:14:32 +05:30
2013-04-26 18:53:36 +05:30
eIter = FEsolving_execElem ( 1 : 2 )
do e = eIter ( 1 ) , eIter ( 2 )
iIter ( 1 : 2 , e ) = FEsolving_execIP ( 1 : 2 , e )
gIter ( 1 : 2 , e ) = [ 1_pInt , homogenization_Ngrains ( mesh_element ( 3 , e ) ) ]
enddo
2014-08-26 20:14:32 +05:30
2013-04-30 17:44:07 +05:30
singleRun = ( eIter ( 1 ) == eIter ( 2 ) . and . iIter ( 1 , eIter ( 1 ) ) == iIter ( 2 , eIter ( 2 ) ) )
2014-05-27 20:16:03 +05:30
!--------------------------------------------------------------------------------------------------
! initialize dotState
if ( . not . singleRun ) then
2014-09-03 01:16:52 +05:30
forall ( p = 1_pInt : size ( plasticState ) )
plasticState ( p ) % previousDotState = 0.0_pReal
2014-05-27 20:16:03 +05:30
plasticState ( p ) % previousDotState2 = 0.0_pReal
end forall
2014-09-03 01:16:52 +05:30
forall ( p = 1_pInt : size ( damageState ) )
damageState ( p ) % previousDotState = 0.0_pReal
2014-06-25 04:51:25 +05:30
damageState ( p ) % previousDotState2 = 0.0_pReal
end forall
2014-09-03 01:16:52 +05:30
forall ( p = 1_pInt : size ( thermalState ) )
thermalState ( p ) % previousDotState = 0.0_pReal
2014-06-25 04:51:25 +05:30
thermalState ( p ) % previousDotState2 = 0.0_pReal
end forall
2014-05-27 20:16:03 +05:30
else
e = eIter ( 1 )
i = iIter ( 1 , e )
2014-07-10 14:17:00 +05:30
do g = gIter ( 1 , e ) , gIter ( 2 , e )
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
plasticState ( p ) % previousDotState ( : , c ) = 0.0_pReal
plasticState ( p ) % previousDotState2 ( : , c ) = 0.0_pReal
damageState ( p ) % previousDotState ( : , c ) = 0.0_pReal
damageState ( p ) % previousDotState2 ( : , c ) = 0.0_pReal
thermalState ( p ) % previousDotState ( : , c ) = 0.0_pReal
thermalState ( p ) % previousDotState2 ( : , c ) = 0.0_pReal
2014-05-27 20:16:03 +05:30
enddo
endif
2013-02-22 04:38:36 +05:30
! --+>> PREGUESS FOR STATE <<+--
2014-08-26 20:14:32 +05:30
2013-11-21 16:28:41 +05:30
! --- DOT STATES ---
2014-08-26 20:14:32 +05:30
2013-11-21 16:28:41 +05:30
!$OMP PARALLEL
2013-02-22 04:38:36 +05:30
!$OMP DO
2014-08-26 20:14:32 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
crystallite_subdt ( g , i , e ) , crystallite_subFrac , g , i , e )
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
2014-07-07 19:51:58 +05:30
2013-02-22 04:38:36 +05:30
!$OMP ENDDO
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) ) then
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , c ) / = plasticState ( p ) % dotState ( : , c ) ) . or . &
any ( damageState ( p ) % dotState ( : , c ) / = damageState ( p ) % dotState ( : , c ) ) . or . &
2014-08-04 23:20:01 +05:30
any ( thermalState ( p ) % dotState ( : , c ) / = thermalState ( p ) % dotState ( : , c ) ) ) then !NaN occured in dotState
2014-07-07 19:51:58 +05:30
2014-05-27 20:16:03 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken is a non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals done (and broken)
!$OMP END CRITICAL (checkTodo)
else ! broken one was local...
crystallite_todo ( g , i , e ) = . false . ! ... done (and broken)
endif
2014-08-26 20:14:32 +05:30
endif
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
2013-10-16 18:34:59 +05:30
! --- UPDATE STATE ---
2014-09-03 01:16:52 +05:30
!$OMP DO PRIVATE(mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState,p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) ) then
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) = plasticState ( p ) % subState0 ( 1 : mySizePlasticDotState , c ) &
2014-06-25 04:51:25 +05:30
+ plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , c ) &
* crystallite_subdt ( g , i , e )
2014-09-03 01:16:52 +05:30
damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) = damageState ( p ) % subState0 ( 1 : mySizeDamageDotState , c ) &
+ damageState ( p ) % dotState ( 1 : mySizeDamageDotState , c ) &
2014-06-25 04:51:25 +05:30
* crystallite_subdt ( g , i , e )
2014-09-03 01:41:57 +05:30
thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) = thermalState ( p ) % subState0 ( 1 : mySizeThermalDotState , c ) &
2014-06-25 04:51:25 +05:30
+ thermalState ( p ) % dotState ( 1 : mySizeThermalDotState , c ) &
* crystallite_subdt ( g , i , e )
2013-02-22 04:38:36 +05:30
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
2013-02-22 04:38:36 +05:30
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --+>> STATE LOOP <<+--
2014-07-09 19:04:33 +05:30
2013-02-22 04:38:36 +05:30
NiterationState = 0_pInt
2014-01-22 00:15:41 +05:30
doneWithIntegration = . false .
crystalliteLooping : do while ( . not . doneWithIntegration . and . NiterationState < nState )
2013-02-22 04:38:36 +05:30
NiterationState = NiterationState + 1_pInt
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP PARALLEL
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- UPDATE DEPENDENT STATES ---
2014-08-26 20:14:32 +05:30
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) &
2014-10-10 17:58:57 +05:30
call constitutive_microstructure ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , &
2014-09-23 16:08:20 +05:30
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , &
2013-02-22 04:38:36 +05:30
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) , g , i , e ) ! update dependent state variables to be consistent with basic states
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
plasticState ( p ) % previousDotState2 ( : , c ) = plasticState ( p ) % previousDotState ( : , c )
damageState ( p ) % previousDotState2 ( : , c ) = damageState ( p ) % previousDotState ( : , c )
thermalState ( p ) % previousDotState2 ( : , c ) = thermalState ( p ) % previousDotState ( : , c )
plasticState ( p ) % previousDotState ( : , c ) = plasticState ( p ) % dotState ( : , c )
damageState ( p ) % previousDotState ( : , c ) = damageState ( p ) % dotState ( : , c )
thermalState ( p ) % previousDotState ( : , c ) = thermalState ( p ) % dotState ( : , c )
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- STRESS INTEGRATION ---
2014-07-09 19:04:33 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
crystallite_todo ( g , i , e ) = crystallite_integrateStress ( g , i , e )
!$OMP FLUSH(crystallite_todo)
2014-08-26 20:14:32 +05:30
if ( . not . crystallite_todo ( g , i , e ) . and . . not . crystallite_localPlasticity ( g , i , e ) ) then ! broken non-local...
!$OMP CRITICAL (checkTodo)
2013-02-22 04:38:36 +05:30
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ... then all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
2013-02-22 04:38:36 +05:30
!$OMP SINGLE
!$OMP CRITICAL (write2out)
2013-10-19 00:27:28 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-02-22 04:38:36 +05:30
write ( 6 , '(a,i8,a)' ) '<< CRYST >> ' , count ( crystallite_todo ( : , : , : ) ) , ' grains todo after stress integration'
!$OMP END CRITICAL (write2out)
!$OMP END SINGLE
2014-08-26 20:14:32 +05:30
2013-10-16 18:34:59 +05:30
! --- DOT STATE ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2014-09-23 16:08:20 +05:30
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) &
2014-09-27 02:19:25 +05:30
call constitutive_collectDotState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , &
crystallite_Fe , &
2014-10-10 17:58:57 +05:30
crystallite_Fp , &
2013-11-21 16:28:41 +05:30
crystallite_subdt ( g , i , e ) , crystallite_subFrac , g , i , e )
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-07-09 19:04:33 +05:30
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(p,c)
2013-02-22 04:38:36 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
2014-09-03 01:16:52 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
if ( any ( plasticState ( p ) % dotState ( : , c ) / = plasticState ( p ) % dotState ( : , c ) ) . or . &
any ( damageState ( p ) % dotState ( : , c ) / = damageState ( p ) % dotState ( : , c ) ) . or . &
any ( thermalState ( p ) % dotState ( : , c ) / = thermalState ( p ) % dotState ( : , c ) ) ) then ! NaN occured in dotState
crystallite_todo ( g , i , e ) = . false . ! ... skip me next time
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if me is non-local...
2014-05-27 20:16:03 +05:30
!$OMP CRITICAL (checkTodo)
2014-09-03 01:16:52 +05:30
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
2014-05-27 20:16:03 +05:30
!$OMP END CRITICAL (checkTodo)
2014-08-26 20:14:32 +05:30
endif
endif
2013-02-22 04:38:36 +05:30
endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
2014-05-27 20:16:03 +05:30
2013-10-16 18:34:59 +05:30
! --- UPDATE STATE ---
2014-07-09 19:04:33 +05:30
2014-06-25 04:51:25 +05:30
!$OMP DO PRIVATE(dot_prod12,dot_prod22, &
!$OMP& mySizePlasticDotState,mySizeDamageDotState,mySizeThermalDotState, &
!$OMP& damageStateResiduum,thermalStateResiduum,damageStateDamper,thermalStateDamper, &
!$OMP& tempDamageState,tempThermalState,p,c, &
2014-09-03 01:16:52 +05:30
!$OMP& statedamper,stateResiduum,tempState)
2013-11-21 16:28:41 +05:30
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
2013-02-22 04:38:36 +05:30
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
2013-10-16 18:34:59 +05:30
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
mySizeDamageDotState = damageState ( p ) % sizeDotState
2014-06-25 04:51:25 +05:30
mySizeThermalDotState = thermalState ( p ) % sizeDotState
2014-09-03 01:16:52 +05:30
dot_prod12 = dot_product ( plasticState ( p ) % dotState ( : , c ) - plasticState ( p ) % previousDotState ( : , c ) , &
2014-06-25 04:51:25 +05:30
plasticState ( p ) % previousDotState ( : , c ) - plasticState ( p ) % previousDotState2 ( : , c ) )
dot_prod22 = dot_product ( plasticState ( p ) % previousDotState ( : , c ) - plasticState ( p ) % previousDotState2 ( : , c ) , &
plasticState ( p ) % previousDotState ( : , c ) - plasticState ( p ) % previousDotState2 ( : , c ) )
2014-05-27 20:16:03 +05:30
if ( dot_prod22 > 0.0_pReal &
. and . ( dot_prod12 < 0.0_pReal &
2014-06-25 04:51:25 +05:30
. or . dot_product ( plasticState ( p ) % dotState ( : , c ) , &
plasticState ( p ) % previousDotState ( : , c ) ) < 0.0_pReal ) ) then
stateDamper = 0.75_pReal + 0.25_pReal * tanh ( 2.0_pReal + 4.0_pReal * dot_prod12 / dot_prod22 )
else
stateDamper = 1.0_pReal
2014-07-07 19:51:58 +05:30
endif
2014-09-03 01:16:52 +05:30
dot_prod12 = dot_product ( damageState ( p ) % dotState ( : , c ) - damageState ( p ) % previousDotState ( : , c ) , &
2014-06-25 04:51:25 +05:30
damageState ( p ) % previousDotState ( : , c ) - damageState ( p ) % previousDotState2 ( : , c ) )
dot_prod22 = dot_product ( damageState ( p ) % previousDotState ( : , c ) - damageState ( p ) % previousDotState2 ( : , c ) , &
damageState ( p ) % previousDotState ( : , c ) - damageState ( p ) % previousDotState2 ( : , c ) )
if ( dot_prod22 > 0.0_pReal &
. and . ( dot_prod12 < 0.0_pReal &
. or . dot_product ( damageState ( p ) % dotState ( : , c ) , &
damageState ( p ) % previousDotState ( : , c ) ) < 0.0_pReal ) ) then
damageStateDamper = 0.75_pReal + 0.25_pReal * tanh ( 2.0_pReal + 4.0_pReal * dot_prod12 / dot_prod22 )
2014-05-27 20:16:03 +05:30
else
2014-06-25 04:51:25 +05:30
damageStateDamper = 1.0_pReal
2014-09-03 01:16:52 +05:30
endif
dot_prod12 = dot_product ( thermalState ( p ) % dotState ( : , c ) - thermalState ( p ) % previousDotState ( : , c ) , &
2014-06-25 04:51:25 +05:30
thermalState ( p ) % previousDotState ( : , c ) - thermalState ( p ) % previousDotState2 ( : , c ) )
dot_prod22 = dot_product ( thermalState ( p ) % previousDotState ( : , c ) - thermalState ( p ) % previousDotState2 ( : , c ) , &
thermalState ( p ) % previousDotState ( : , c ) - thermalState ( p ) % previousDotState2 ( : , c ) )
if ( dot_prod22 > 0.0_pReal &
. and . ( dot_prod12 < 0.0_pReal &
. or . dot_product ( thermalState ( p ) % dotState ( : , c ) , &
thermalState ( p ) % previousDotState ( : , c ) ) < 0.0_pReal ) ) then
thermalStateDamper = 0.75_pReal + 0.25_pReal * tanh ( 2.0_pReal + 4.0_pReal * dot_prod12 / dot_prod22 )
else
thermalStateDamper = 1.0_pReal
2014-08-26 20:14:32 +05:30
endif
2014-05-27 20:16:03 +05:30
! --- get residui ---
2014-08-26 20:14:32 +05:30
2014-06-25 04:51:25 +05:30
stateResiduum ( 1 : mySizePlasticDotState ) = plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) &
- plasticState ( p ) % subState0 ( 1 : mySizePlasticDotState , c ) &
- ( plasticState ( p ) % dotState ( 1 : mySizePlasticDotState , c ) * stateDamper &
2014-09-03 01:16:52 +05:30
+ plasticState ( p ) % previousDotState ( 1 : mySizePlasticDotState , c ) &
2014-06-25 04:51:25 +05:30
* ( 1.0_pReal - stateDamper ) ) * crystallite_subdt ( g , i , e )
2014-08-26 20:14:32 +05:30
2014-06-25 04:51:25 +05:30
damageStateResiduum ( 1 : mySizeDamageDotState ) = damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) &
- damageState ( p ) % subState0 ( 1 : mySizeDamageDotState , c ) &
- ( damageState ( p ) % dotState ( 1 : mySizeDamageDotState , c ) * damageStateDamper &
2014-09-03 01:16:52 +05:30
+ damageState ( p ) % previousDotState ( 1 : mySizeDamageDotState , c ) &
2014-06-25 04:51:25 +05:30
* ( 1.0_pReal - damageStatedamper ) ) * crystallite_subdt ( g , i , e )
2014-08-26 20:14:32 +05:30
2014-06-25 04:51:25 +05:30
thermalStateResiduum ( 1 : mySizeThermalDotState ) = thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) &
- thermalState ( p ) % subState0 ( 1 : mySizeThermalDotState , c ) &
- ( thermalState ( p ) % dotState ( 1 : mySizeThermalDotState , c ) * thermalStateDamper &
2014-09-03 01:16:52 +05:30
+ thermalState ( p ) % previousDotState ( 1 : mySizeThermalDotState , c ) &
2014-06-25 04:51:25 +05:30
* ( 1.0_pReal - thermalStateDamper ) ) * crystallite_subdt ( g , i , e )
2014-05-27 20:16:03 +05:30
! --- correct state with residuum ---
2014-06-25 04:51:25 +05:30
tempState ( 1 : mySizePlasticDotState ) = plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) &
- stateResiduum ( 1 : mySizePlasticDotState ) ! need to copy to local variable, since we cant flush a pointer in openmp
tempDamageState ( 1 : mySizeDamageDotState ) = damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) &
- damageStateResiduum ( 1 : mySizeDamageDotState ) ! need to copy to local variable, since we cant flush a pointer in openmp
tempThermalState ( 1 : mySizeThermalDotState ) = thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) &
- thermalStateResiduum ( 1 : mySizeThermalDotState ) ! need to copy to local variable, since we cant flush a pointer in openmp
2012-05-17 20:55:21 +05:30
#ifndef _OPENMP
2014-05-15 18:31:54 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
2013-02-22 04:38:36 +05:30
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i3,/)' ) '<< CRYST >> update state at el ip g ' , e , i , g
write ( 6 , '(a,f6.1,/)' ) '<< CRYST >> statedamper ' , statedamper
2014-07-07 19:51:58 +05:30
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> state residuum' , stateResiduum ( 1 : mySizePlasticDotState )
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> new state' , tempState ( 1 : mySizePlasticDotState )
2013-02-22 04:38:36 +05:30
endif
2012-05-17 20:55:21 +05:30
#endif
2013-02-22 04:38:36 +05:30
! --- store corrected dotState --- (cannot do this before state update, because not sure how to flush pointers in openmp)
2014-05-27 20:16:03 +05:30
2014-06-25 04:51:25 +05:30
plasticState ( p ) % dotState ( : , c ) = plasticState ( p ) % dotState ( : , c ) * stateDamper &
+ plasticState ( p ) % previousDotState ( : , c ) &
2014-07-07 19:51:58 +05:30
* ( 1.0_pReal - stateDamper )
2014-09-03 01:16:52 +05:30
damageState ( p ) % dotState ( : , c ) = damageState ( p ) % dotState ( : , c ) * damageStateDamper &
2014-06-25 04:51:25 +05:30
+ damageState ( p ) % previousDotState ( : , c ) &
2014-08-26 20:14:32 +05:30
* ( 1.0_pReal - damageStateDamper )
2014-06-25 04:51:25 +05:30
thermalState ( p ) % dotState ( : , c ) = thermalState ( p ) % dotState ( : , c ) * thermalStateDamper &
+ thermalState ( p ) % previousDotState ( : , c ) &
2014-07-07 19:51:58 +05:30
* ( 1.0_pReal - thermalStateDamper )
2014-05-27 20:16:03 +05:30
! --- converged ? ---
2014-07-07 19:51:58 +05:30
if ( all ( abs ( stateResiduum ( 1 : mySizePlasticDotState ) ) < plasticState ( p ) % aTolState ( 1 : mySizePlasticDotState ) &
. or . abs ( stateResiduum ( 1 : mySizePlasticDotState ) ) < rTol_crystalliteState &
* abs ( tempState ( 1 : mySizePlasticDotState ) ) ) &
. and . all ( abs ( damageStateResiduum ( 1 : mySizeDamageDotState ) ) < damageState ( p ) % aTolState ( 1 : mySizeDamageDotState ) &
. or . abs ( damageStateResiduum ( 1 : mySizeDamageDotState ) ) < rTol_crystalliteState &
* abs ( tempDamageState ( 1 : mySizeDamageDotState ) ) ) &
2014-06-25 04:51:25 +05:30
. and . all ( abs ( thermalStateResiduum ( 1 : mySizeThermalDotState ) ) < thermalState ( p ) % aTolState ( 1 : mySizeThermalDotState ) &
. or . abs ( thermalStateResiduum ( 1 : mySizeThermalDotState ) ) < rTol_crystalliteState &
2014-07-07 19:51:58 +05:30
* abs ( tempThermalState ( 1 : mySizeThermalDotState ) ) ) ) then
2014-06-25 04:51:25 +05:30
crystallite_converged ( g , i , e ) = . true . ! ... converged per definition
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
!$OMP CRITICAL (distributionState)
debug_StateLoopDistribution ( NiterationState , numerics_integrationMode ) = &
debug_StateLoopDistribution ( NiterationState , numerics_integrationMode ) + 1_pInt
!$OMP END CRITICAL (distributionState)
endif
endif
2014-09-03 01:16:52 +05:30
plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) = tempState ( 1 : mySizePlasticDotState )
damageState ( p ) % state ( 1 : mySizeDamageDotState , c ) = tempDamageState ( 1 : mySizeDamageDotState )
thermalState ( p ) % state ( 1 : mySizeThermalDotState , c ) = tempThermalState ( 1 : mySizeThermalDotState )
2014-05-27 20:16:03 +05:30
endif
2013-02-22 04:38:36 +05:30
enddo ; enddo ; enddo
!$OMP ENDDO
! --- STATE JUMP ---
2014-07-09 19:04:33 +05:30
2013-02-22 04:38:36 +05:30
!$OMP DO
do e = eIter ( 1 ) , eIter ( 2 ) ; do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
!$OMP FLUSH(crystallite_todo)
if ( crystallite_todo ( g , i , e ) . and . crystallite_converged ( g , i , e ) ) then ! converged and still alive...
2014-08-26 20:14:32 +05:30
crystallite_todo ( g , i , e ) = crystallite_stateJump ( g , i , e )
2013-02-22 04:38:36 +05:30
!$OMP FLUSH(crystallite_todo)
if ( . not . crystallite_todo ( g , i , e ) ) then ! if state jump fails, then convergence is broken
2014-08-26 20:14:32 +05:30
crystallite_converged ( g , i , e ) = . false .
2013-02-22 04:38:36 +05:30
if ( . not . crystallite_localPlasticity ( g , i , e ) ) then ! if broken non-local...
!$OMP CRITICAL (checkTodo)
crystallite_todo = crystallite_todo . and . crystallite_localPlasticity ! ...all non-locals skipped
!$OMP END CRITICAL (checkTodo)
endif
endif
endif
enddo ; enddo ; enddo
!$OMP ENDDO
!$OMP END PARALLEL
2014-08-26 20:14:32 +05:30
2014-05-27 20:16:03 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) &
2013-05-17 23:22:46 +05:30
write ( 6 , '(a,i8,a,i2,/)' ) '<< CRYST >> ' , count ( crystallite_converged ( : , : , : ) ) , &
2014-08-27 21:24:11 +05:30
' grains converged after state integration #' , NiterationState
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- NON-LOCAL CONVERGENCE CHECK ---
2014-08-26 20:14:32 +05:30
if ( . not . singleRun ) then ! if not requesting Integration of just a single IP
2013-10-19 00:27:28 +05:30
if ( any ( . not . crystallite_converged . and . . not . crystallite_localPlasticity ) ) & ! any non-local not yet converged (or broken)...
2013-02-22 04:38:36 +05:30
crystallite_converged = crystallite_converged . and . crystallite_localPlasticity ! ...restart all non-local as not converged
endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt ) then
2013-04-29 16:47:30 +05:30
write ( 6 , '(a,i8,a)' ) '<< CRYST >> ' , count ( crystallite_converged ( : , : , : ) ) , &
' grains converged after non-local check'
write ( 6 , '(a,i8,a,i2,/)' ) '<< CRYST >> ' , count ( crystallite_todo ( : , : , : ) ) , &
2014-08-27 21:24:11 +05:30
' grains todo after state integration #' , NiterationState
2013-02-22 04:38:36 +05:30
endif
2014-01-22 00:15:41 +05:30
! --- CHECK IF DONE WITH INTEGRATION ---
doneWithIntegration = . true .
elemLoop : do e = eIter ( 1 ) , eIter ( 2 )
do i = iIter ( 1 , e ) , iIter ( 2 , e ) ; do g = gIter ( 1 , e ) , gIter ( 2 , e ) ! iterate over elements, ips and grains
if ( crystallite_todo ( g , i , e ) . and . . not . crystallite_converged ( g , i , e ) ) then
doneWithIntegration = . false .
exit elemLoop
endif
enddo ; enddo
enddo elemLoop
2013-05-17 23:22:46 +05:30
enddo crystalliteLooping
2012-03-09 01:55:28 +05:30
end subroutine crystallite_integrateStateFPI
2010-10-01 17:48:49 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculates a jump in the state according to the current state and the current stress
2014-06-17 12:24:49 +05:30
!> returns true, if state jump was successfull or not needed. false indicates NaN in delta state
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-04-29 16:47:30 +05:30
logical function crystallite_stateJump ( g , i , e )
use debug , only : &
debug_level , &
debug_crystallite , &
debug_levelExtensive , &
debug_levelSelective , &
debug_e , &
debug_i , &
debug_g
2013-11-21 16:28:41 +05:30
use FEsolving , only : &
2014-08-26 20:14:32 +05:30
FEsolving_execElem , &
2013-11-21 16:28:41 +05:30
FEsolving_execIP
use mesh , only : &
mesh_element , &
mesh_NcpElems
use material , only : &
2014-05-27 20:16:03 +05:30
plasticState , &
2014-06-25 04:51:25 +05:30
damageState , &
thermalState , &
2014-06-23 00:28:29 +05:30
mappingConstitutive , &
2013-11-21 16:28:41 +05:30
homogenization_Ngrains
use constitutive , only : &
2014-08-26 20:14:32 +05:30
constitutive_collectDeltaState
2014-07-02 17:57:39 +05:30
2013-02-22 04:38:36 +05:30
implicit none
2013-11-21 16:28:41 +05:30
integer ( pInt ) , intent ( in ) :: &
e , & ! element index
i , & ! integration point index
g ! grain index
2014-06-25 04:51:25 +05:30
2013-11-21 16:28:41 +05:30
integer ( pInt ) :: &
2014-06-25 04:51:25 +05:30
c , &
p , &
2014-09-03 01:16:52 +05:30
mySizePlasticDotState
2014-07-02 17:57:39 +05:30
2014-08-26 20:14:32 +05:30
c = mappingConstitutive ( 1 , g , i , e )
p = mappingConstitutive ( 2 , g , i , e )
2014-07-02 17:57:39 +05:30
if ( constitutive_collectDeltaState ( crystallite_Tstar_v ( 1 : 6 , g , i , e ) , g , i , e ) ) then
2014-06-25 04:51:25 +05:30
mySizePlasticDotState = plasticState ( p ) % sizeDotState
2014-07-02 17:57:39 +05:30
if ( any ( plasticState ( p ) % deltaState ( : , c ) / = plasticState ( p ) % deltaState ( : , c ) ) ) then ! NaN occured in deltaState
2014-06-17 12:24:49 +05:30
crystallite_stateJump = . false .
return
endif
2014-06-25 04:51:25 +05:30
plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) = plasticState ( p ) % state ( 1 : mySizePlasticDotState , c ) + &
plasticState ( p ) % deltaState ( 1 : mySizePlasticDotState , c )
2014-07-23 18:56:05 +05:30
2012-06-06 20:41:30 +05:30
#ifndef _OPENMP
2014-08-26 20:14:32 +05:30
p = mappingConstitutive ( 2 , g , i , e )
c = mappingConstitutive ( 1 , g , i , e )
2014-07-23 18:56:05 +05:30
if ( any ( plasticState ( p ) % deltaState ( 1 : mySizePlasticDotState , c ) / = 0.0_pReal ) &
2014-06-17 12:24:49 +05:30
. and . iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
write ( 6 , '(a,i8,1x,i2,1x,i3, /)' ) '<< CRYST >> update state at el ip g ' , e , i , g
2014-07-23 18:56:05 +05:30
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> deltaState' , plasticState ( p ) % deltaState ( 1 : mySizePlasticDotState , c )
write ( 6 , '(a,/,(12x,12(e12.5,1x)),/)' ) '<< CRYST >> new state' , plasticState ( p ) % state ( 1 : mySizePlasticDotState , c )
2014-06-17 12:24:49 +05:30
endif
#endif
endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
crystallite_stateJump = . true .
2014-08-26 20:14:32 +05:30
2012-06-06 20:41:30 +05:30
end function crystallite_stateJump
2014-09-10 14:07:12 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Map 2nd order tensor to reference config
!--------------------------------------------------------------------------------------------------
function crystallite_push33ToRef ( g , i , e , tensor33 )
use math , only : &
math_inv33
implicit none
real ( pReal ) , dimension ( 3 , 3 ) :: crystallite_push33ToRef
real ( pReal ) , dimension ( 3 , 3 ) , intent ( in ) :: tensor33
real ( pReal ) , dimension ( 3 , 3 ) :: invFp
integer ( pInt ) , intent ( in ) :: &
e , & ! element index
i , & ! integration point index
g ! grain index
invFp = math_inv33 ( crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) )
crystallite_push33ToRef = matmul ( invFp , matmul ( tensor33 , transpose ( invFp ) ) )
end function crystallite_push33ToRef
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2014-08-26 20:14:32 +05:30
!> @brief calculation of stress (P) with time integration based on a residuum in Lp and
!> intermediate acceleration of the Newton-Raphson correction
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
2013-04-29 16:47:30 +05:30
logical function crystallite_integrateStress ( &
2013-02-22 04:38:36 +05:30
g , & ! grain number
i , & ! integration point number
e , & ! element number
timeFraction &
)
use prec , only : pLongInt
use numerics , only : nStress , &
aTol_crystalliteStress , &
rTol_crystalliteStress , &
iJacoLpresiduum , &
numerics_integrationMode
use debug , only : debug_level , &
debug_crystallite , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_e , &
debug_i , &
debug_g , &
debug_cumLpCalls , &
debug_cumLpTicks , &
debug_StressLoopDistribution
use constitutive , only : constitutive_LpAndItsTangent , &
2014-10-20 21:13:28 +05:30
constitutive_TandItsTangent , &
constitutive_getThermalStrain
2013-02-22 04:38:36 +05:30
use math , only : math_mul33x33 , &
math_mul33xx33 , &
math_mul66x6 , &
math_mul99x99 , &
math_transpose33 , &
math_inv33 , &
math_invert33 , &
math_invert , &
math_det33 , &
math_norm33 , &
math_I3 , &
math_identity2nd , &
math_Mandel66to3333 , &
math_Mandel6to33 , &
math_Mandel33to6 , &
math_Plain3333to99 , &
math_Plain33to9 , &
math_Plain9to33
2014-09-09 20:48:49 +05:30
use mesh , only : mesh_element
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
implicit none
integer ( pInt ) , intent ( in ) :: e , & ! element index
i , & ! integration point index
g ! grain index
real ( pReal ) , optional , intent ( in ) :: timeFraction ! fraction of timestep
2013-04-29 16:47:30 +05:30
2013-02-22 04:38:36 +05:30
!*** local variables ***!
real ( pReal ) , dimension ( 3 , 3 ) :: Fg_new , & ! deformation gradient at end of timestep
Fp_current , & ! plastic deformation gradient at start of timestep
Fp_new , & ! plastic deformation gradient at end of timestep
Fe_new , & ! elastic deformation gradient at end of timestep
invFp_new , & ! inverse of Fp_new
invFp_current , & ! inverse of Fp_current
Lpguess , & ! current guess for plastic velocity gradient
Lpguess_old , & ! known last good guess for plastic velocity gradient
Lp_constitutive , & ! plastic velocity gradient resulting from constitutive law
residuum , & ! current residuum of plastic velocity gradient
residuum_old , & ! last residuum of plastic velocity gradient
deltaLp , & ! direction of next guess
Tstar , & ! 2nd Piola-Kirchhoff Stress
A , &
B , &
2014-10-20 21:13:28 +05:30
Fe , & ! elastic deformation gradient
Fi , & ! gradient of intermediate deformation stages
Ci , & ! stretch of intermediate deformation stages
invFi
2013-02-22 04:38:36 +05:30
real ( pReal ) , dimension ( 6 ) :: Tstar_v ! 2nd Piola-Kirchhoff Stress in Mandel-Notation
real ( pReal ) , dimension ( 9 ) :: work ! needed for matrix inversion by LAPACK
integer ( pInt ) , dimension ( 9 ) :: ipiv ! needed for matrix inversion by LAPACK
real ( pReal ) , dimension ( 9 , 9 ) :: dLp_dT_constitutive , & ! partial derivative of plastic velocity gradient calculated by constitutive law
dT_dFe_constitutive , & ! partial derivative of 2nd Piola-Kirchhoff stress calculated by constitutive law
dFe_dLp , & ! partial derivative of elastic deformation gradient
dR_dLp , & ! partial derivative of residuum (Jacobian for NEwton-Raphson scheme)
dR_dLp2 ! working copy of dRdLp
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: dT_dFe3333 , & ! partial derivative of 2nd Piola-Kirchhoff stress
dFe_dLp3333 ! partial derivative of elastic deformation gradient
2014-01-21 21:39:00 +05:30
real ( pReal ) det , & ! determinant
2014-08-26 20:14:32 +05:30
steplength0 , &
steplength , &
2013-02-22 04:38:36 +05:30
dt , & ! time increment
2014-10-20 21:13:28 +05:30
aTol , &
detFi
2013-02-22 04:38:36 +05:30
logical error ! flag indicating an error
integer ( pInt ) NiterationStress , & ! number of stress integrations
ierr , & ! error indicator for LAPACK
o , &
p , &
jacoCounter ! counter to check for Jacobian update
integer ( pLongInt ) tick , &
tock , &
tickrate , &
maxticks
2013-10-19 00:27:28 +05:30
2013-06-11 22:05:04 +05:30
external :: &
2013-10-19 00:27:28 +05:30
#if(FLOAT==8)
2013-06-11 22:05:04 +05:30
dgesv
#elif(FLOAT==4)
sgesv
#endif
2013-02-22 04:38:36 +05:30
!* be pessimistic
crystallite_integrateStress = . false .
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
write ( 6 , '(a,i8,1x,i2,1x,i3)' ) '<< CRYST >> integrateStress at el ip g ' , e , i , g
endif
2011-03-29 12:57:19 +05:30
#endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* only integrate over fraction of timestep?
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
if ( present ( timeFraction ) ) then
dt = crystallite_subdt ( g , i , e ) * timeFraction
2013-11-21 16:28:41 +05:30
Fg_new = crystallite_subF0 ( 1 : 3 , 1 : 3 , g , i , e ) &
+ ( crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e ) - crystallite_subF0 ( 1 : 3 , 1 : 3 , g , i , e ) ) * timeFraction
2014-08-26 20:14:32 +05:30
else
2013-02-22 04:38:36 +05:30
dt = crystallite_subdt ( g , i , e )
Fg_new = crystallite_subF ( 1 : 3 , 1 : 3 , g , i , e )
endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* feed local variables
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
Fp_current = crystallite_subFp0 ( 1 : 3 , 1 : 3 , g , i , e ) ! "Fp_current" is only used as temp var here...
Lpguess_old = crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) ! consider present Lp good (i.e. worth remembering) ...
Lpguess = crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) ! ... and take it as first guess
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* inversion of Fp_current...
2014-08-26 20:14:32 +05:30
invFp_current = math_inv33 ( Fp_current )
2013-02-22 04:38:36 +05:30
if ( all ( invFp_current == 0.0_pReal ) ) then ! ... failed?
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
2014-08-27 21:24:11 +05:30
write ( 6 , '(a,i8,1x,a,i8,a,1x,i2,1x,i3)' ) '<< CRYST >> integrateStress failed on inversion of Fp_current at el (elFE) ip g ' , &
e , '(' , mesh_element ( 1 , e ) , ')' , i , g
2013-10-19 00:27:28 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) > 0_pInt ) &
write ( 6 , '(/,a,/,3(12x,3(f12.7,1x)/))' ) '<< CRYST >> Fp_current' , math_transpose33 ( Fp_current ( 1 : 3 , 1 : 3 ) )
2013-02-22 04:38:36 +05:30
endif
2011-03-29 12:57:19 +05:30
#endif
2013-02-22 04:38:36 +05:30
return
endif
A = math_mul33x33 ( Fg_new , invFp_current ) ! intermediate tensor needed later to calculate dFe_dLp
2014-10-20 21:13:28 +05:30
Fi = math_I3 ! intermediate configuration, assume decomposition as F = Fe Fi Fp
Fi = math_mul33x33 ( Fi , constitutive_getThermalStrain ( g , i , e ) )
Ci = math_mul33x33 ( math_transpose33 ( Fi ) , Fi ) ! non-plastic stretch tensor (neglecting elastic contributions)
invFi = math_inv33 ( Fi )
detFi = math_det33 ( Fi )
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* start LpLoop with normal step length
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
NiterationStress = 0_pInt
jacoCounter = 0_pInt
steplength0 = 1.0_pReal
steplength = steplength0
residuum_old = 0.0_pReal
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
LpLoop : do
NiterationStress = NiterationStress + 1_pInt
2013-10-19 00:27:28 +05:30
loopsExeced : if ( NiterationStress > nStress ) then
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-10-19 00:27:28 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) &
2014-08-27 21:24:11 +05:30
write ( 6 , '(a,i3,a,i8,1x,a,i8,a,1x,i2,1x,i3,/)' ) '<< CRYST >> integrateStress reached loop limit' , nStress , &
' at el (elFE) ip g ' , e , mesh_element ( 1 , e ) , i , g
2011-03-29 12:57:19 +05:30
#endif
2013-02-22 04:38:36 +05:30
return
2013-10-19 00:27:28 +05:30
endif loopsExeced
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* calculate (elastic) 2nd Piola--Kirchhoff stress tensor and its tangent from constitutive law
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
B = math_I3 - dt * Lpguess
2014-10-20 21:13:28 +05:30
Fe = math_mul33x33 ( math_mul33x33 ( A , B ) , invFi ) ! current elastic deformation tensor
call constitutive_TandItsTangent ( Tstar , dT_dFe3333 , Fe , g , i , e ) ! call constitutive law to calculate 2nd Piola-Kirchhoff stress and its derivative in unloaded configuration
Tstar = math_mul33x33 ( Ci , math_mul33x33 ( invFi , &
math_mul33x33 ( Tstar , math_transpose33 ( invFi ) ) ) ) / detFi ! push Tstar forward to plastic (lattice) configuration
2013-02-22 04:38:36 +05:30
Tstar_v = math_Mandel33to6 ( Tstar )
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* calculate plastic velocity gradient and its tangent from constitutive law
2014-08-26 20:14:32 +05:30
2013-11-21 16:28:41 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
2013-02-22 04:38:36 +05:30
call system_clock ( count = tick , count_rate = tickrate , count_max = maxticks )
2013-11-21 16:28:41 +05:30
endif
2014-08-26 20:14:32 +05:30
2013-11-21 16:28:41 +05:30
call constitutive_LpAndItsTangent ( Lp_constitutive , dLp_dT_constitutive , Tstar_v , &
2014-10-10 17:58:57 +05:30
g , i , e )
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
call system_clock ( count = tock , count_rate = tickrate , count_max = maxticks )
!$OMP CRITICAL (debugTimingLpTangent)
debug_cumLpCalls = debug_cumLpCalls + 1_pInt
debug_cumLpTicks = debug_cumLpTicks + tock - tick
!$OMP FLUSH (debug_cumLpTicks)
if ( tock < tick ) debug_cumLpTicks = debug_cumLpTicks + maxticks
!$OMP END CRITICAL (debugTimingLpTangent)
endif
2014-08-26 20:14:32 +05:30
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
2013-10-19 00:27:28 +05:30
write ( 6 , '(a,i3,/)' ) '<< CRYST >> iteration ' , NiterationStress
2013-02-22 04:38:36 +05:30
write ( 6 , '(a,/,3(12x,3(e20.7,1x)/))' ) '<< CRYST >> Lp_constitutive' , math_transpose33 ( Lp_constitutive )
write ( 6 , '(a,/,3(12x,3(e20.7,1x)/))' ) '<< CRYST >> Lpguess' , math_transpose33 ( Lpguess )
endif
2011-03-29 12:57:19 +05:30
#endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* update current residuum and check for convergence of loop
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
aTol = max ( rTol_crystalliteStress * max ( math_norm33 ( Lpguess ) , math_norm33 ( Lp_constitutive ) ) , & ! absolute tolerance from largest acceptable relative error
aTol_crystalliteStress ) ! minimum lower cutoff
residuum = Lpguess - Lp_constitutive
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
if ( any ( residuum / = residuum ) ) then ! NaN in residuum...
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-10-19 00:27:28 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) &
2014-08-27 21:24:11 +05:30
write ( 6 , '(a,i8,1x,a,i8,a,1x,i2,1x,i3,a,i3,a)' ) '<< CRYST >> integrateStress encountered NaN at el (elFE) ip g ' , &
e , mesh_element ( 1 , e ) , i , g , &
' ; iteration ' , NiterationStress , &
' >> returning..!'
2011-03-29 12:57:19 +05:30
#endif
2013-02-22 04:38:36 +05:30
return ! ...me = .false. to inform integrator about problem
elseif ( math_norm33 ( residuum ) < aTol ) then ! converged if below absolute tolerance
exit LpLoop ! ...leave iteration loop
elseif ( math_norm33 ( residuum ) < math_norm33 ( residuum_old ) . or . NiterationStress == 1_pInt ) then ! not converged, but improved norm of residuum (always proceed in first iteration)...
residuum_old = residuum ! ...remember old values and...
2014-08-26 20:14:32 +05:30
Lpguess_old = Lpguess
2013-02-22 04:38:36 +05:30
steplength = steplength0 ! ...proceed with normal step length (calculate new search direction)
else ! not converged and residuum not improved...
steplength = 0.5_pReal * steplength ! ...try with smaller step length in same direction
Lpguess = Lpguess_old + steplength * deltaLp
cycle LpLoop
endif
2014-08-26 20:14:32 +05:30
!* calculate Jacobian for correction term
2013-02-22 04:38:36 +05:30
if ( mod ( jacoCounter , iJacoLpresiduum ) == 0_pInt ) then
dFe_dLp3333 = 0.0_pReal
do o = 1_pInt , 3_pInt ; do p = 1_pInt , 3_pInt
2014-01-22 14:08:13 +05:30
dFe_dLp3333 ( o , p , 1 : 3 , p ) = A ( o , 1 : 3 ) ! dFe_dLp(i,j,k,l) = -dt * A(i,k) delta(l,j)
2013-02-22 04:38:36 +05:30
enddo ; enddo
dFe_dLp3333 = - dt * dFe_dLp3333
dFe_dLp = math_Plain3333to99 ( dFe_dLp3333 )
dT_dFe_constitutive = math_Plain3333to99 ( dT_dFe3333 )
dR_dLp = math_identity2nd ( 9_pInt ) - &
2014-08-26 20:14:32 +05:30
math_mul99x99 ( dLp_dT_constitutive , math_mul99x99 ( dT_dFe_constitutive , dFe_dLp ) )
2013-02-22 04:38:36 +05:30
dR_dLp2 = dR_dLp ! will be overwritten in first call to LAPACK routine
work = math_plain33to9 ( residuum )
2012-08-28 22:29:45 +05:30
#if(FLOAT==8)
2013-02-22 04:38:36 +05:30
call dgesv ( 9 , 1 , dR_dLp2 , 9 , ipiv , work , 9 , ierr ) ! solve dR/dLp * delta Lp = -res for dR/dLp
2012-08-28 22:29:45 +05:30
#elif(FLOAT==4)
2013-02-22 04:38:36 +05:30
call sgesv ( 9 , 1 , dR_dLp2 , 9 , ipiv , work , 9 , ierr ) ! solve dR/dLp * delta Lp = -res for dR/dLp
2012-08-28 22:29:45 +05:30
#endif
2013-02-22 04:38:36 +05:30
if ( ierr / = 0_pInt ) then
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
2014-08-27 21:24:11 +05:30
write ( 6 , '(a,i8,1x,a,i8,a,1x,i2,1x,i3,a,i3)' ) '<< CRYST >> integrateStress failed on dR/dLp inversion at el ip g ' , &
e , mesh_element ( 1 , e ) , i , g
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
write ( 6 , * )
write ( 6 , '(a,/,9(12x,9(e15.3,1x)/))' ) '<< CRYST >> dR_dLp' , transpose ( dR_dLp )
write ( 6 , '(a,/,9(12x,9(e15.3,1x)/))' ) '<< CRYST >> dFe_dLp' , transpose ( dFe_dLp )
write ( 6 , '(a,/,9(12x,9(e15.3,1x)/))' ) '<< CRYST >> dT_dFe_constitutive' , transpose ( dT_dFe_constitutive )
write ( 6 , '(a,/,9(12x,9(e15.3,1x)/))' ) '<< CRYST >> dLp_dT_constitutive' , transpose ( dLp_dT_constitutive )
write ( 6 , '(a,/,3(12x,3(e20.7,1x)/))' ) '<< CRYST >> A' , math_transpose33 ( A )
write ( 6 , '(a,/,3(12x,3(e20.7,1x)/))' ) '<< CRYST >> B' , math_transpose33 ( B )
write ( 6 , '(a,/,3(12x,3(e20.7,1x)/))' ) '<< CRYST >> Lp_constitutive' , math_transpose33 ( Lp_constitutive )
write ( 6 , '(a,/,3(12x,3(e20.7,1x)/))' ) '<< CRYST >> Lpguess' , math_transpose33 ( Lpguess )
endif
endif
2011-08-02 16:59:08 +05:30
#endif
2013-02-22 04:38:36 +05:30
return
endif
deltaLp = - math_plain9to33 ( work )
endif
jacoCounter = jacoCounter + 1_pInt ! increase counter for jaco update
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
Lpguess = Lpguess + steplength * deltaLp
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
enddo LpLoop
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* calculate new plastic and elastic deformation gradient
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
invFp_new = math_mul33x33 ( invFp_current , B )
2013-11-21 16:28:41 +05:30
invFp_new = invFp_new / math_det33 ( invFp_new ) ** ( 1.0_pReal / 3.0_pReal ) ! regularize by det
2013-02-22 04:38:36 +05:30
call math_invert33 ( invFp_new , Fp_new , det , error )
2013-11-21 16:28:41 +05:30
if ( error . or . any ( Fp_new / = Fp_new ) ) then
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
2014-08-27 21:24:11 +05:30
write ( 6 , '(a,i8,1x,a,i8,a,1x,i2,1x,i3,a,i3)' ) '<< CRYST >> integrateStress failed on invFp_new inversion at el ip g ' , &
e , mesh_element ( 1 , e ) , i , g , ' ; iteration ' , NiterationStress
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
2013-10-19 00:27:28 +05:30
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) &
write ( 6 , '(/,a,/,3(12x,3(f12.7,1x)/))' ) '<< CRYST >> invFp_new' , math_transpose33 ( invFp_new )
2013-02-22 04:38:36 +05:30
endif
2011-03-29 12:57:19 +05:30
#endif
2013-02-22 04:38:36 +05:30
return
endif
2014-10-20 21:13:28 +05:30
Fe_new = math_mul33x33 ( math_mul33x33 ( Fg_new , invFp_new ) , invFi ) ! calc resulting Fe
2014-08-26 20:14:32 +05:30
2014-01-16 16:06:40 +05:30
!* calculate 1st Piola-Kirchhoff stress
2014-08-26 20:14:32 +05:30
2014-10-20 21:13:28 +05:30
crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) = math_mul33x33 ( math_mul33x33 ( Fe_new , Fi ) , &
math_mul33x33 ( math_Mandel6to33 ( Tstar_v ) , &
math_transpose33 ( invFp_new ) ) ) * detFi
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* store local values in global variables
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) = Lpguess
crystallite_Tstar_v ( 1 : 6 , g , i , e ) = Tstar_v
crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) = Fp_new
crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) = Fe_new
crystallite_invFp ( 1 : 3 , 1 : 3 , g , i , e ) = invFp_new
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!* set return flag to true
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
crystallite_integrateStress = . true .
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( e == debug_e . and . i == debug_i . and . g == debug_g ) &
2014-08-26 20:14:32 +05:30
. or . . not . iand ( debug_level ( debug_crystallite ) , debug_levelSelective ) / = 0_pInt ) ) then
2014-08-27 21:24:11 +05:30
write ( 6 , '(a,/,3(12x,3(f12.7,1x)/))' ) '<< CRYST >> P / MPa' , math_transpose33 ( crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) ) * 1.0e-6_pReal
2013-02-22 04:38:36 +05:30
write ( 6 , '(a,/,3(12x,3(f12.7,1x)/))' ) '<< CRYST >> Cauchy / MPa' , &
2014-08-27 21:24:11 +05:30
math_mul33x33 ( crystallite_P ( 1 : 3 , 1 : 3 , g , i , e ) , math_transpose33 ( Fg_new ) ) * 1.0e-6_pReal / math_det33 ( Fg_new )
2013-02-22 04:38:36 +05:30
write ( 6 , '(a,/,3(12x,3(f12.7,1x)/))' ) '<< CRYST >> Fe Lp Fe^-1' , &
math_transpose33 ( math_mul33x33 ( Fe_new , math_mul33x33 ( crystallite_Lp ( 1 : 3 , 1 : 3 , g , i , e ) , math_inv33 ( Fe_new ) ) ) ) ! transpose to get correct print out order
write ( 6 , '(a,/,3(12x,3(f12.7,1x)/))' ) '<< CRYST >> Fp' , math_transpose33 ( crystallite_Fp ( 1 : 3 , 1 : 3 , g , i , e ) )
endif
2011-03-29 12:57:19 +05:30
#endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
if ( iand ( debug_level ( debug_crystallite ) , debug_levelBasic ) / = 0_pInt ) then
!$OMP CRITICAL (distributionStress)
debug_StressLoopDistribution ( NiterationStress , numerics_integrationMode ) = &
debug_StressLoopDistribution ( NiterationStress , numerics_integrationMode ) + 1_pInt
!$OMP END CRITICAL (distributionStress)
endif
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
end function crystallite_integrateStress
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculates orientations and disorientations (in case of single grain ips)
!--------------------------------------------------------------------------------------------------
2012-03-09 01:55:28 +05:30
subroutine crystallite_orientations
2013-11-21 16:28:41 +05:30
use math , only : &
math_pDecomposition , &
math_RtoQ , &
math_qConj
use FEsolving , only : &
2014-08-26 20:14:32 +05:30
FEsolving_execElem , &
2013-11-21 16:28:41 +05:30
FEsolving_execIP
use IO , only : &
IO_warning
use material , only : &
material_phase , &
homogenization_Ngrains , &
2014-09-03 01:16:52 +05:30
plasticState
2013-11-21 16:28:41 +05:30
use mesh , only : &
mesh_element , &
mesh_ipNeighborhood , &
FE_NipNeighbors , &
FE_geomtype , &
FE_celltype
2014-02-28 18:58:27 +05:30
use lattice , only : &
2014-03-09 02:20:31 +05:30
lattice_qDisorientation , &
lattice_structure
2013-11-21 16:28:41 +05:30
use constitutive_nonlocal , only : &
constitutive_nonlocal_updateCompatibility
2014-07-02 17:57:39 +05:30
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
implicit none
2013-11-21 16:28:41 +05:30
integer ( pInt ) &
e , & ! element index
i , & ! integration point index
g , & ! grain index
2014-08-26 20:14:32 +05:30
n , & ! neighbor index
2013-11-21 16:28:41 +05:30
neighboring_e , & ! element index of my neighbor
neighboring_i , & ! integration point index of my neighbor
myPhase , & ! phase
2014-03-12 05:25:40 +05:30
neighboringPhase
2013-11-21 16:28:41 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: &
U , &
R
real ( pReal ) , dimension ( 4 ) :: &
orientation
logical &
error
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- CALCULATE ORIENTATION AND LATTICE ROTATION ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
!$OMP PARALLEL DO PRIVATE(error,U,R,orientation)
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
do g = 1_pInt , homogenization_Ngrains ( mesh_element ( 3 , e ) )
2014-07-02 17:57:39 +05:30
! somehow this subroutine is not threadsafe, so need critical statement here; not clear, what exactly the problem is
2014-08-26 20:14:32 +05:30
!$OMP CRITICAL (polarDecomp)
2014-07-02 17:57:39 +05:30
call math_pDecomposition ( crystallite_Fe ( 1 : 3 , 1 : 3 , g , i , e ) , U , R , error ) ! polar decomposition of Fe
2013-02-27 16:02:37 +05:30
!$OMP END CRITICAL (polarDecomp)
2013-02-22 04:38:36 +05:30
if ( error ) then
call IO_warning ( 650_pInt , e , i , g )
2014-07-02 17:57:39 +05:30
orientation = [ 1.0_pReal , 0.0_pReal , 0.0_pReal , 0.0_pReal ] ! fake orientation
2013-02-22 04:38:36 +05:30
else
orientation = math_RtoQ ( transpose ( R ) )
endif
2014-02-28 18:58:27 +05:30
crystallite_rotation ( 1 : 4 , g , i , e ) = lattice_qDisorientation ( crystallite_orientation0 ( 1 : 4 , g , i , e ) , & ! active rotation from ori0
2014-03-09 02:20:31 +05:30
orientation ) ! to current orientation (with no symmetry)
2013-02-22 04:38:36 +05:30
crystallite_orientation ( 1 : 4 , g , i , e ) = orientation
enddo
enddo
enddo
!$OMP END PARALLEL DO
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- UPDATE SOME ADDITIONAL VARIABLES THAT ARE NEEDED FOR NONLOCAL MATERIAL ---
2014-03-12 05:25:40 +05:30
! --- we use crystallite_orientation from above, so need a separate loop
2014-08-26 20:14:32 +05:30
2014-03-12 20:59:14 +05:30
!$OMP PARALLEL DO PRIVATE(myPhase,neighboring_e,neighboring_i,neighboringPhase)
2013-02-22 04:38:36 +05:30
do e = FEsolving_execElem ( 1 ) , FEsolving_execElem ( 2 )
do i = FEsolving_execIP ( 1 , e ) , FEsolving_execIP ( 2 , e )
2014-09-03 01:16:52 +05:30
myPhase = material_phase ( 1 , i , e ) ! get my phase (non-local models make no sense with more than one grain per material point)
if ( plasticState ( myPhase ) % nonLocal ) then ! if nonlocal model
2013-02-22 04:38:36 +05:30
! --- calculate disorientation between me and my neighbor ---
2014-08-26 20:14:32 +05:30
2013-04-22 19:05:35 +05:30
do n = 1_pInt , FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , e ) ) ) ) ! loop through my neighbors
2013-02-22 04:38:36 +05:30
neighboring_e = mesh_ipNeighborhood ( 1 , n , i , e )
neighboring_i = mesh_ipNeighborhood ( 2 , n , i , e )
2014-03-12 20:59:14 +05:30
if ( neighboring_e > 0 . and . neighboring_i > 0 ) then ! if neighbor exists
2013-02-22 04:38:36 +05:30
neighboringPhase = material_phase ( 1 , neighboring_i , neighboring_e ) ! get my neighbor's phase
2014-09-03 01:16:52 +05:30
if ( plasticState ( neighboringPhase ) % nonLocal ) then ! neighbor got also nonlocal plasticity
2014-03-12 05:25:40 +05:30
if ( lattice_structure ( myPhase ) == lattice_structure ( neighboringPhase ) ) then ! if my neighbor has same crystal structure like me
2013-02-22 04:38:36 +05:30
crystallite_disorientation ( : , n , 1 , i , e ) = &
2014-02-28 18:58:27 +05:30
lattice_qDisorientation ( crystallite_orientation ( 1 : 4 , 1 , i , e ) , &
2014-08-26 20:14:32 +05:30
crystallite_orientation ( 1 : 4 , 1 , neighboring_i , neighboring_e ) , &
2014-03-12 05:25:40 +05:30
lattice_structure ( myPhase ) ) ! calculate disorientation for given symmetry
2013-02-22 04:38:36 +05:30
else ! for neighbor with different phase
2013-11-21 16:28:41 +05:30
crystallite_disorientation ( : , n , 1 , i , e ) = [ 0.0_pReal , 1.0_pReal , 0.0_pReal , 0.0_pReal ] ! 180 degree rotation about 100 axis
2013-02-22 04:38:36 +05:30
endif
else ! for neighbor with local plasticity
2013-11-21 16:28:41 +05:30
crystallite_disorientation ( : , n , 1 , i , e ) = [ - 1.0_pReal , 0.0_pReal , 0.0_pReal , 0.0_pReal ] ! homomorphic identity
2013-02-22 04:38:36 +05:30
endif
else ! no existing neighbor
2013-11-21 16:28:41 +05:30
crystallite_disorientation ( : , n , 1 , i , e ) = [ - 1.0_pReal , 0.0_pReal , 0.0_pReal , 0.0_pReal ] ! homomorphic identity
2013-02-22 04:38:36 +05:30
endif
enddo
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
! --- calculate compatibility and transmissivity between me and my neighbor ---
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
call constitutive_nonlocal_updateCompatibility ( crystallite_orientation , i , e )
2014-08-26 20:14:32 +05:30
2013-02-22 04:38:36 +05:30
endif
enddo
enddo
!$OMP END PARALLEL DO
2014-08-26 20:14:32 +05:30
2012-03-09 01:55:28 +05:30
end subroutine crystallite_orientations
2009-12-18 21:16:33 +05:30
2013-02-22 04:38:36 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief return results of particular grain
!--------------------------------------------------------------------------------------------------
2013-10-16 18:34:59 +05:30
function crystallite_postResults ( ipc , ip , el )
2013-05-08 17:32:30 +05:30
use math , only : &
math_qToEuler , &
2013-06-07 15:05:00 +05:30
math_qToEulerAxisAngle , &
2013-05-08 17:32:30 +05:30
math_mul33x33 , &
math_transpose33 , &
math_det33 , &
math_I3 , &
inDeg , &
math_Mandel6to33 , &
math_qMul , &
math_qConj
use mesh , only : &
mesh_element , &
mesh_ipVolume , &
mesh_ipCoordinates , &
mesh_maxNipNeighbors , &
mesh_ipNeighborhood , &
FE_NipNeighbors , &
FE_geomtype , &
FE_celltype
use material , only : &
2014-06-30 20:17:30 +05:30
plasticState , &
damageState , &
thermalState , &
2013-05-08 17:32:30 +05:30
microstructure_crystallite , &
crystallite_Noutput , &
material_phase , &
material_texture , &
homogenization_Ngrains
use constitutive , only : &
2014-09-03 01:16:52 +05:30
constitutive_homogenizedC , &
constitutive_postResults
2014-08-26 20:14:32 +05:30
2009-05-07 21:57:36 +05:30
implicit none
2013-11-21 16:28:41 +05:30
integer ( pInt ) , intent ( in ) :: &
el , & !< element index
ip , & !< integration point index
ipc !< grain index
2009-05-07 21:57:36 +05:30
2014-08-10 16:44:43 +05:30
#ifdef multiphysicsOut
real ( pReal ) , dimension ( 1 + crystallite_sizePostResults ( microstructure_crystallite ( mesh_element ( 4 , el ) ) ) + &
1 + plasticState ( material_phase ( ipc , ip , el ) ) % sizePostResults + &
2014-09-26 20:46:10 +05:30
damageState ( material_phase ( ipc , ip , el ) ) % sizePostResults + &
thermalState ( material_phase ( ipc , ip , el ) ) % sizePostResults ) :: &
2014-08-10 16:44:43 +05:30
crystallite_postResults
#else
2013-05-08 17:32:30 +05:30
real ( pReal ) , dimension ( 1 + crystallite_sizePostResults ( microstructure_crystallite ( mesh_element ( 4 , el ) ) ) + &
2014-08-11 19:03:17 +05:30
1 + plasticState ( material_phase ( ipc , ip , el ) ) % sizePostResults ) :: &
2013-11-21 16:28:41 +05:30
crystallite_postResults
2014-08-10 16:44:43 +05:30
#endif
2013-11-21 16:28:41 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: &
Ee
real ( pReal ) , dimension ( 4 ) :: &
rotation
real ( pReal ) :: &
detF
integer ( pInt ) :: &
o , &
c , &
crystID , &
mySize , &
n
2014-09-23 16:08:20 +05:30
2010-02-25 23:09:11 +05:30
2013-05-08 17:32:30 +05:30
crystID = microstructure_crystallite ( mesh_element ( 4 , el ) )
2010-02-25 23:09:11 +05:30
crystallite_postResults = 0.0_pReal
c = 0_pInt
2013-05-08 23:18:00 +05:30
crystallite_postResults ( c + 1 ) = real ( crystallite_sizePostResults ( crystID ) , pReal ) ! size of results from cryst
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
c = c + 1_pInt
2014-08-26 20:14:32 +05:30
2012-02-21 22:01:37 +05:30
do o = 1_pInt , crystallite_Noutput ( crystID )
2011-08-01 23:40:55 +05:30
mySize = 0_pInt
2013-12-12 22:39:59 +05:30
select case ( crystallite_outputID ( o , crystID ) )
case ( phase_ID )
2011-08-01 23:40:55 +05:30
mySize = 1_pInt
2013-10-16 18:34:59 +05:30
crystallite_postResults ( c + 1 ) = real ( material_phase ( ipc , ip , el ) , pReal ) ! phaseID of grain
2013-12-12 22:39:59 +05:30
case ( texture_ID )
2011-08-01 23:40:55 +05:30
mySize = 1_pInt
2013-10-16 18:34:59 +05:30
crystallite_postResults ( c + 1 ) = real ( material_texture ( ipc , ip , el ) , pReal ) ! textureID of grain
2013-12-12 22:39:59 +05:30
case ( volume_ID )
2011-08-01 23:40:55 +05:30
mySize = 1_pInt
2013-10-16 18:34:59 +05:30
detF = math_det33 ( crystallite_partionedF ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) ! V_current = det(F) * V_reference
2013-11-21 16:28:41 +05:30
crystallite_postResults ( c + 1 ) = detF * mesh_ipVolume ( ip , el ) &
/ homogenization_Ngrains ( mesh_element ( 3 , el ) ) ! grain volume (not fraction but absolute)
2013-12-12 22:39:59 +05:30
case ( orientation_ID )
2011-08-01 23:40:55 +05:30
mySize = 4_pInt
2013-10-16 18:34:59 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = crystallite_orientation ( 1 : 4 , ipc , ip , el ) ! grain orientation as quaternion
2013-12-12 22:39:59 +05:30
case ( eulerangles_ID )
2011-08-01 23:40:55 +05:30
mySize = 3_pInt
2013-11-21 16:28:41 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = inDeg &
* math_qToEuler ( crystallite_orientation ( 1 : 4 , ipc , ip , el ) ) ! grain orientation as Euler angles in degree
2013-12-12 22:39:59 +05:30
case ( grainrotation_ID )
2011-08-01 23:40:55 +05:30
mySize = 4_pInt
2013-06-07 15:05:00 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = &
2013-10-16 18:34:59 +05:30
math_qToEulerAxisAngle ( crystallite_rotation ( 1 : 4 , ipc , ip , el ) ) ! grain rotation away from initial orientation as axis-angle in sample reference coordinates
2013-10-19 00:27:28 +05:30
crystallite_postResults ( c + 4 ) = inDeg * crystallite_postResults ( c + 4 ) ! angle in degree
2013-12-12 22:39:59 +05:30
case ( grainrotationx_ID )
2013-01-16 14:15:41 +05:30
mySize = 1_pInt
2013-10-16 18:34:59 +05:30
rotation = math_qToEulerAxisAngle ( crystallite_rotation ( 1 : 4 , ipc , ip , el ) ) ! grain rotation away from initial orientation as axis-angle in sample reference coordinates
2013-10-19 00:27:28 +05:30
crystallite_postResults ( c + 1 ) = inDeg * rotation ( 1 ) * rotation ( 4 ) ! angle in degree
2013-12-12 22:39:59 +05:30
case ( grainrotationy_ID )
2013-01-16 14:15:41 +05:30
mySize = 1_pInt
2013-10-16 18:34:59 +05:30
rotation = math_qToEulerAxisAngle ( crystallite_rotation ( 1 : 4 , ipc , ip , el ) ) ! grain rotation away from initial orientation as axis-angle in sample reference coordinates
2013-10-19 00:27:28 +05:30
crystallite_postResults ( c + 1 ) = inDeg * rotation ( 2 ) * rotation ( 4 ) ! angle in degree
2013-12-12 22:39:59 +05:30
case ( grainrotationz_ID )
2013-01-16 14:15:41 +05:30
mySize = 1_pInt
2013-10-16 18:34:59 +05:30
rotation = math_qToEulerAxisAngle ( crystallite_rotation ( 1 : 4 , ipc , ip , el ) ) ! grain rotation away from initial orientation as axis-angle in sample reference coordinates
2013-10-19 00:27:28 +05:30
crystallite_postResults ( c + 1 ) = inDeg * rotation ( 3 ) * rotation ( 4 ) ! angle in degree
2011-05-11 22:08:45 +05:30
! remark: tensor output is of the form 11,12,13, 21,22,23, 31,32,33
! thus row index i is slow, while column index j is fast. reminder: "row is slow"
2014-08-26 20:14:32 +05:30
2013-12-12 22:39:59 +05:30
case ( defgrad_ID )
2010-05-18 13:27:13 +05:30
mySize = 9_pInt
2013-05-08 23:18:00 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = &
2013-10-16 18:34:59 +05:30
reshape ( math_transpose33 ( crystallite_partionedF ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( e_ID )
2012-01-20 15:55:35 +05:30
mySize = 9_pInt
crystallite_postResults ( c + 1 : c + mySize ) = 0.5_pReal * reshape ( ( math_mul33x33 ( &
2013-10-16 18:34:59 +05:30
math_transpose33 ( crystallite_partionedF ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) , &
crystallite_partionedF ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) - math_I3 ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( fe_ID )
2010-05-18 13:27:13 +05:30
mySize = 9_pInt
2013-05-08 23:18:00 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = &
2013-10-16 18:34:59 +05:30
reshape ( math_transpose33 ( crystallite_Fe ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( ee_ID )
2013-10-16 18:34:59 +05:30
Ee = 0.5_pReal * ( math_mul33x33 ( math_transpose33 ( crystallite_Fe ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) , &
crystallite_Fe ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) - math_I3 )
2010-05-18 13:27:13 +05:30
mySize = 9_pInt
2012-02-16 00:28:38 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = reshape ( Ee , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( fp_ID )
2010-05-18 13:27:13 +05:30
mySize = 9_pInt
2013-05-08 23:18:00 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = &
2013-10-16 18:34:59 +05:30
reshape ( math_transpose33 ( crystallite_Fp ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( lp_ID )
2011-02-25 13:45:26 +05:30
mySize = 9_pInt
2013-05-08 23:18:00 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = &
2013-10-16 18:34:59 +05:30
reshape ( math_transpose33 ( crystallite_Lp ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( p_ID )
2010-05-18 13:27:13 +05:30
mySize = 9_pInt
2013-05-08 23:18:00 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = &
2013-10-16 18:34:59 +05:30
reshape ( math_transpose33 ( crystallite_P ( 1 : 3 , 1 : 3 , ipc , ip , el ) ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( s_ID )
2010-05-18 13:27:13 +05:30
mySize = 9_pInt
2013-05-08 23:18:00 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = &
2013-10-16 18:34:59 +05:30
reshape ( math_Mandel6to33 ( crystallite_Tstar_v ( 1 : 6 , ipc , ip , el ) ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( elasmatrix_ID )
2012-03-01 18:36:09 +05:30
mySize = 36_pInt
2013-10-16 18:34:59 +05:30
crystallite_postResults ( c + 1 : c + mySize ) = reshape ( constitutive_homogenizedC ( ipc , ip , el ) , [ mySize ] )
2013-12-12 22:39:59 +05:30
case ( neighboringelement_ID )
2013-05-08 17:32:30 +05:30
mySize = mesh_maxNipNeighbors
crystallite_postResults ( c + 1 : c + mySize ) = 0.0_pReal
forall ( n = 1_pInt : FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , el ) ) ) ) ) &
crystallite_postResults ( c + n ) = real ( mesh_ipNeighborhood ( 1 , n , ip , el ) , pReal )
2013-12-12 22:39:59 +05:30
case ( neighboringip_ID )
2013-05-08 17:32:30 +05:30
mySize = mesh_maxNipNeighbors
crystallite_postResults ( c + 1 : c + mySize ) = 0.0_pReal
forall ( n = 1_pInt : FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , el ) ) ) ) ) &
crystallite_postResults ( c + n ) = real ( mesh_ipNeighborhood ( 2 , n , ip , el ) , pReal )
2010-02-25 23:09:11 +05:30
end select
2011-08-01 23:40:55 +05:30
c = c + mySize
2010-02-25 23:09:11 +05:30
enddo
2011-05-11 22:08:45 +05:30
2014-06-30 20:17:30 +05:30
crystallite_postResults ( c + 1 ) = real ( plasticState ( material_phase ( ipc , ip , el ) ) % sizePostResults , pReal ) ! size of constitutive results
c = c + 1_pInt
2014-09-23 16:08:20 +05:30
if ( size ( crystallite_postResults ) - c > 0_pInt ) &
crystallite_postResults ( c + 1 : size ( crystallite_postResults ) ) = &
2014-06-30 20:17:30 +05:30
constitutive_postResults ( crystallite_Tstar_v ( 1 : 6 , ipc , ip , el ) , crystallite_Fe , &
2014-10-10 17:58:57 +05:30
ipc , ip , el )
2014-06-25 04:51:25 +05:30
2012-03-09 01:55:28 +05:30
end function crystallite_postResults
2009-05-07 21:57:36 +05:30
2014-05-12 18:30:37 +05:30
2013-02-22 04:38:36 +05:30
end module crystallite