2012-10-02 18:23:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-03-06 20:11:15 +05:30
|
|
|
! $Id$
|
2012-10-02 18:23:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
2013-03-06 20:11:15 +05:30
|
|
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
2012-10-02 18:23:25 +05:30
|
|
|
!> @brief elasticity, plasticity, internal microstructure state
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
module constitutive
|
2013-01-16 15:44:57 +05:30
|
|
|
use prec, only: &
|
|
|
|
pInt, &
|
|
|
|
pReal, &
|
|
|
|
p_vec
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
private
|
|
|
|
type(p_vec), public, dimension(:,:,:), allocatable :: &
|
2013-09-19 13:16:01 +05:30
|
|
|
constitutive_state0, & !< pointer array to microstructure at start of BVP inc
|
2013-01-16 15:44:57 +05:30
|
|
|
constitutive_partionedState0, & !< pointer array to microstructure at start of homogenization inc
|
|
|
|
constitutive_subState0, & !< pointer array to microstructure at start of crystallite inc
|
|
|
|
constitutive_state, & !< pointer array to current microstructure (end of converged time step)
|
|
|
|
constitutive_state_backup, & !< pointer array to backed up microstructure (end of converged time step)
|
|
|
|
constitutive_dotState, & !< pointer array to evolution of current microstructure
|
|
|
|
constitutive_deltaState, & !< pointer array to incremental change of current microstructure
|
|
|
|
constitutive_previousDotState,& !< pointer array to previous evolution of current microstructure
|
|
|
|
constitutive_previousDotState2,& !< pointer array to 2nd previous evolution of current microstructure
|
|
|
|
constitutive_dotState_backup, & !< pointer array to backed up evolution of current microstructure
|
|
|
|
constitutive_RK4dotState, & !< pointer array to evolution of microstructure defined by classical Runge-Kutta method
|
|
|
|
constitutive_aTolState !< pointer array to absolute state tolerance
|
|
|
|
type(p_vec), public, dimension(:,:,:,:), allocatable :: &
|
|
|
|
constitutive_RKCK45dotState !< pointer array to evolution of microstructure used by Cash-Karp Runge-Kutta method
|
|
|
|
integer(pInt), public, dimension(:,:,:), allocatable :: &
|
|
|
|
constitutive_sizeDotState, & !< size of dotState array
|
|
|
|
constitutive_sizeState, & !< size of state array per grain
|
|
|
|
constitutive_sizePostResults !< size of postResults array per grain
|
|
|
|
integer(pInt), public :: &
|
|
|
|
constitutive_maxSizeDotState, &
|
|
|
|
constitutive_maxSizePostResults
|
|
|
|
integer(pInt), private :: &
|
|
|
|
constitutive_maxSizeState
|
|
|
|
|
|
|
|
public :: &
|
|
|
|
constitutive_init, &
|
|
|
|
constitutive_homogenizedC, &
|
|
|
|
constitutive_microstructure, &
|
|
|
|
constitutive_LpAndItsTangent, &
|
|
|
|
constitutive_TandItsTangent, &
|
|
|
|
constitutive_collectDotState, &
|
|
|
|
constitutive_collectDeltaState, &
|
|
|
|
constitutive_postResults
|
|
|
|
|
|
|
|
private :: &
|
|
|
|
constitutive_hooke_TandItsTangent
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
contains
|
2012-10-02 18:23:25 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief allocates arrays pointing to array of the various constitutive modules
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
subroutine constitutive_init
|
2014-03-12 13:03:51 +05:30
|
|
|
#ifdef HDF
|
|
|
|
use hdf5, only: &
|
|
|
|
HID_T
|
|
|
|
use IO, only : &
|
2014-03-12 22:21:01 +05:30
|
|
|
HDF5_mappingConstitutive
|
2014-03-12 13:03:51 +05:30
|
|
|
#endif
|
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2013-01-16 15:44:57 +05:30
|
|
|
use debug, only: &
|
|
|
|
debug_level, &
|
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
|
|
|
use numerics, only: &
|
|
|
|
numerics_integrator
|
|
|
|
use IO, only: &
|
|
|
|
IO_error, &
|
|
|
|
IO_open_file, &
|
|
|
|
IO_open_jobFile_stat, &
|
|
|
|
IO_write_jobFile, &
|
2013-09-18 19:37:55 +05:30
|
|
|
IO_write_jobIntFile, &
|
2013-02-25 22:04:59 +05:30
|
|
|
IO_timeStamp
|
2013-01-16 15:44:57 +05:30
|
|
|
use mesh, only: &
|
|
|
|
mesh_maxNips, &
|
|
|
|
mesh_NcpElems, &
|
|
|
|
mesh_element, &
|
|
|
|
FE_Nips, &
|
|
|
|
FE_geomtype
|
|
|
|
use material, only: &
|
|
|
|
material_phase, &
|
|
|
|
material_Nphase, &
|
|
|
|
material_localFileExt, &
|
|
|
|
material_configFile, &
|
|
|
|
phase_name, &
|
|
|
|
phase_elasticity, &
|
|
|
|
phase_plasticity, &
|
|
|
|
phase_plasticityInstance, &
|
|
|
|
phase_Noutput, &
|
|
|
|
homogenization_Ngrains, &
|
2013-11-27 13:34:05 +05:30
|
|
|
homogenization_maxNgrains, &
|
|
|
|
ELASTICITY_HOOKE_ID, &
|
|
|
|
PLASTICITY_NONE_ID, &
|
|
|
|
PLASTICITY_J2_ID, &
|
|
|
|
PLASTICITY_PHENOPOWERLAW_ID, &
|
|
|
|
PLASTICITY_DISLOTWIN_ID, &
|
|
|
|
PLASTICITY_TITANMOD_ID, &
|
|
|
|
PLASTICITY_NONLOCAL_ID ,&
|
|
|
|
ELASTICITY_HOOKE_label, &
|
|
|
|
PLASTICITY_NONE_label, &
|
|
|
|
PLASTICITY_J2_label, &
|
|
|
|
PLASTICITY_PHENOPOWERLAW_label, &
|
|
|
|
PLASTICITY_DISLOTWIN_label, &
|
|
|
|
PLASTICITY_TITANMOD_label, &
|
|
|
|
PLASTICITY_NONLOCAL_label
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none
|
2012-03-09 01:55:28 +05:30
|
|
|
use constitutive_j2
|
|
|
|
use constitutive_phenopowerlaw
|
|
|
|
use constitutive_titanmod
|
|
|
|
use constitutive_dislotwin
|
|
|
|
use constitutive_nonlocal
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
implicit none
|
2013-12-12 22:39:59 +05:30
|
|
|
integer(pInt), parameter :: FILEUNIT = 200_pInt
|
2013-01-16 15:44:57 +05:30
|
|
|
integer(pInt) :: &
|
|
|
|
g, & !< grain number
|
|
|
|
i, & !< integration point number
|
|
|
|
e, & !< element number
|
2013-09-19 13:16:01 +05:30
|
|
|
cMax, & !< maximum number of grains
|
2013-01-16 15:44:57 +05:30
|
|
|
iMax, & !< maximum number of integration points
|
|
|
|
eMax, & !< maximum number of elements
|
2014-02-28 15:48:40 +05:30
|
|
|
phase, &
|
2013-01-16 15:44:57 +05:30
|
|
|
s, &
|
2014-02-28 15:48:40 +05:30
|
|
|
instance,&
|
2013-01-16 15:44:57 +05:30
|
|
|
myNgrains
|
|
|
|
integer(pInt), dimension(:,:), pointer :: thisSize
|
|
|
|
character(len=64), dimension(:,:), pointer :: thisOutput
|
2013-11-27 13:34:05 +05:30
|
|
|
character(len=32) :: outputName !< name of output, intermediate fix until HDF5 output is ready
|
2013-05-24 19:13:44 +05:30
|
|
|
logical :: knownPlasticity, nonlocalConstitutionPresent
|
2014-03-12 13:03:51 +05:30
|
|
|
#ifdef HDF
|
2014-03-26 14:11:45 +05:30
|
|
|
integer(pInt) :: &
|
|
|
|
phase !< phase
|
2014-03-12 22:21:01 +05:30
|
|
|
integer(pInt), dimension(:,:,:), allocatable :: mappingConstitutive
|
|
|
|
integer(pInt), dimension(:,:,:), allocatable :: mappingCrystallite
|
|
|
|
integer(pInt), dimension(:), allocatable :: ConstitutivePosition
|
|
|
|
integer(pInt), dimension(:), allocatable :: CrystallitePosition
|
|
|
|
allocate(mappingConstitutive(homogenization_maxngrains,mesh_ncpelems,2),source=0_pInt)
|
|
|
|
allocate(mappingCrystallite (homogenization_maxngrains,mesh_ncpelems,2),source=0_pInt)
|
|
|
|
allocate(ConstitutivePosition(material_nphase),source=0_pInt)
|
|
|
|
allocate(CrystallitePosition(material_nphase),source=0_pInt)
|
2014-03-12 13:03:51 +05:30
|
|
|
#endif
|
2013-05-24 19:13:44 +05:30
|
|
|
nonlocalConstitutionPresent = .false.
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! parse plasticities from config file
|
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
|
2014-03-09 02:20:31 +05:30
|
|
|
if (any(phase_plasticity == PLASTICITY_NONE_ID)) call constitutive_none_init(FILEUNIT)
|
|
|
|
if (any(phase_plasticity == PLASTICITY_J2_ID)) call constitutive_j2_init(FILEUNIT)
|
|
|
|
if (any(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)) call constitutive_phenopowerlaw_init(FILEUNIT)
|
|
|
|
if (any(phase_plasticity == PLASTICITY_TITANMOD_ID)) call constitutive_titanmod_init(FILEUNIT)
|
|
|
|
if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call constitutive_dislotwin_init(FILEUNIT)
|
2014-03-11 23:10:59 +05:30
|
|
|
if (any(phase_plasticity == PLASTICITY_NONLOCAL_ID)) call constitutive_nonlocal_init(FILEUNIT)
|
2013-12-12 22:39:59 +05:30
|
|
|
close(FILEUNIT)
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2013-05-28 23:01:55 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- constitutive init -+>>>'
|
|
|
|
write(6,'(a)') ' $Id$'
|
2013-05-08 14:53:47 +05:30
|
|
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
2012-10-09 18:04:57 +05:30
|
|
|
#include "compilation_info.f90"
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write description file for constitutive phase output
|
2013-12-12 22:39:59 +05:30
|
|
|
call IO_write_jobFile(FILEUNIT,'outputConstitutive')
|
2014-02-28 15:48:40 +05:30
|
|
|
do phase = 1_pInt,material_Nphase
|
|
|
|
instance = phase_plasticityInstance(phase) ! which instance of a plasticity is present phase
|
2013-01-16 15:44:57 +05:30
|
|
|
knownPlasticity = .true. ! assume valid
|
2014-02-28 15:48:40 +05:30
|
|
|
select case(phase_plasticity(phase)) ! split per constititution
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONE_ID)
|
|
|
|
outputName = PLASTICITY_NONE_label
|
2014-03-13 12:13:49 +05:30
|
|
|
thisOutput => null() ! constitutive_none_output
|
|
|
|
thisSize => null() ! constitutive_none_sizePostResult
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_J2_ID)
|
|
|
|
outputName = PLASTICITY_J2_label
|
2013-01-16 15:44:57 +05:30
|
|
|
thisOutput => constitutive_j2_output
|
|
|
|
thisSize => constitutive_j2_sizePostResult
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_PHENOPOWERLAW_ID)
|
2013-12-18 12:58:01 +05:30
|
|
|
outputName = PLASTICITY_PHENOPOWERLAW_label
|
2013-01-16 15:44:57 +05:30
|
|
|
thisOutput => constitutive_phenopowerlaw_output
|
|
|
|
thisSize => constitutive_phenopowerlaw_sizePostResult
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_DISLOTWIN_ID)
|
|
|
|
outputName = PLASTICITY_DISLOTWIN_label
|
2013-01-16 15:44:57 +05:30
|
|
|
thisOutput => constitutive_dislotwin_output
|
|
|
|
thisSize => constitutive_dislotwin_sizePostResult
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_TITANMOD_ID)
|
|
|
|
outputName = PLASTICITY_TITANMOD_label
|
|
|
|
thisOutput => constitutive_titanmod_output
|
|
|
|
thisSize => constitutive_titanmod_sizePostResult
|
|
|
|
case (PLASTICITY_NONLOCAL_ID)
|
|
|
|
outputName = PLASTICITY_NONLOCAL_label
|
2013-01-16 15:44:57 +05:30
|
|
|
thisOutput => constitutive_nonlocal_output
|
|
|
|
thisSize => constitutive_nonlocal_sizePostResult
|
|
|
|
case default
|
|
|
|
knownPlasticity = .false.
|
|
|
|
end select
|
2014-02-28 15:48:40 +05:30
|
|
|
write(FILEUNIT,'(/,a,/)') '['//trim(phase_name(phase))//']'
|
2013-01-16 15:44:57 +05:30
|
|
|
if (knownPlasticity) then
|
2013-12-12 22:39:59 +05:30
|
|
|
write(FILEUNIT,'(a)') '(plasticity)'//char(9)//trim(outputName)
|
2014-03-05 13:36:21 +05:30
|
|
|
do e = 1_pInt,phase_Noutput(phase)
|
2014-02-28 15:48:40 +05:30
|
|
|
write(FILEUNIT,'(a,i4)') trim(thisOutput(e,instance))//char(9),thisSize(e,instance)
|
2013-01-16 15:44:57 +05:30
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
enddo
|
2013-12-12 22:39:59 +05:30
|
|
|
close(FILEUNIT)
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! allocation of states
|
2013-09-19 13:16:01 +05:30
|
|
|
cMax = homogenization_maxNgrains
|
2013-01-16 15:44:57 +05:30
|
|
|
iMax = mesh_maxNips
|
|
|
|
eMax = mesh_NcpElems
|
|
|
|
|
2013-12-12 22:39:59 +05:30
|
|
|
allocate(constitutive_state0(cMax,iMax,eMax))
|
2013-09-19 13:16:01 +05:30
|
|
|
allocate(constitutive_partionedState0(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_subState0(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_state(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_state_backup(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_dotState(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_deltaState(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_dotState_backup(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_aTolState(cMax,iMax,eMax))
|
2013-12-12 22:39:59 +05:30
|
|
|
allocate(constitutive_sizeDotState(cMax,iMax,eMax), source=0_pInt)
|
|
|
|
allocate(constitutive_sizeState(cMax,iMax,eMax), source=0_pInt)
|
|
|
|
allocate(constitutive_sizePostResults(cMax,iMax,eMax), source=0_pInt)
|
2013-01-16 15:44:57 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2013-09-19 13:16:01 +05:30
|
|
|
allocate(constitutive_previousDotState(cMax,iMax,eMax))
|
|
|
|
allocate(constitutive_previousDotState2(cMax,iMax,eMax))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2013-09-19 13:16:01 +05:30
|
|
|
allocate(constitutive_RK4dotState(cMax,iMax,eMax))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
2013-09-19 13:16:01 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(6,cMax,iMax,eMax))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
|
|
|
|
do e = 1_pInt,mesh_NcpElems ! loop over elements
|
|
|
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
|
|
|
do i = 1_pInt,FE_Nips(FE_geomtype(mesh_element(2,e))) ! loop over IPs
|
|
|
|
do g = 1_pInt,myNgrains ! loop over grains
|
2013-11-27 13:34:05 +05:30
|
|
|
select case(phase_elasticity(material_phase(g,i,e)))
|
|
|
|
case default ! so far no output for elasticity
|
2013-01-16 15:44:57 +05:30
|
|
|
end select
|
2014-02-28 15:48:40 +05:30
|
|
|
instance = phase_plasticityInstance(material_phase(g,i,e))
|
2014-03-12 13:03:51 +05:30
|
|
|
#ifdef HDF
|
2014-03-26 14:11:45 +05:30
|
|
|
ConstitutivePosition(instance) = ConstitutivePosition(instance)+1_pInt
|
|
|
|
mappingConstitutive(g,e,1:2) = [ConstitutivePosition(instance),instance]
|
2014-03-12 13:03:51 +05:30
|
|
|
#endif
|
2013-11-27 13:34:05 +05:30
|
|
|
select case(phase_plasticity(material_phase(g,i,e)))
|
|
|
|
case (PLASTICITY_NONE_ID)
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_none_sizeState(instance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_none_sizeState(instance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_none_sizeState(instance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_none_sizeState(instance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_none_sizeState(instance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_none_sizeState(instance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_none_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_none_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_none_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_none_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_none_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_none_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_none_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
enddo
|
|
|
|
endif
|
2013-10-14 16:24:45 +05:30
|
|
|
constitutive_state0(g,i,e)%p = 0.0_pReal
|
|
|
|
constitutive_aTolState(g,i,e)%p = 1.0_pReal
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_sizeState(g,i,e) = 0_pInt
|
|
|
|
constitutive_sizeDotState(g,i,e) = 0_pInt
|
|
|
|
constitutive_sizePostResults(g,i,e) = 0_pInt
|
|
|
|
case (PLASTICITY_J2_ID)
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_j2_sizeState(instance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_j2_sizeState(instance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_j2_sizeState(instance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_j2_sizeState(instance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_j2_sizeState(instance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_j2_sizeState(instance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_j2_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_j2_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_j2_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_j2_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_j2_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_j2_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_j2_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
enddo
|
|
|
|
endif
|
2014-02-28 15:48:40 +05:30
|
|
|
constitutive_state0(g,i,e)%p = constitutive_j2_stateInit(instance)
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_j2_aTolState(instance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_j2_sizeState(instance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_j2_sizeDotState(instance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_j2_sizePostResults(instance)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_PHENOPOWERLAW_ID)
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_phenopowerlaw_sizeState(instance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_phenopowerlaw_sizeState(instance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_phenopowerlaw_sizeState(instance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_phenopowerlaw_sizeState(instance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_phenopowerlaw_sizeState(instance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_phenopowerlaw_sizeState(instance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
enddo
|
|
|
|
endif
|
2014-02-28 15:48:40 +05:30
|
|
|
constitutive_state0(g,i,e)%p = constitutive_phenopowerlaw_stateInit(instance)
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_phenopowerlaw_aTolState(instance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_phenopowerlaw_sizeState(instance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_phenopowerlaw_sizeDotState(instance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_phenopowerlaw_sizePostResults(instance)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_DISLOTWIN_ID)
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_dislotwin_sizeState(instance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_dislotwin_sizeState(instance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_dislotwin_sizeState(instance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_dislotwin_sizeState(instance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_dislotwin_sizeState(instance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_dislotwin_sizeState(instance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_dislotwin_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_dislotwin_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_dislotwin_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_dislotwin_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
enddo
|
|
|
|
endif
|
2014-03-09 02:20:31 +05:30
|
|
|
constitutive_state0(g,i,e)%p = constitutive_dislotwin_stateInit(instance,material_phase(g,i,e))
|
2014-02-28 15:48:40 +05:30
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_dislotwin_aTolState(instance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_dislotwin_sizeState(instance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_dislotwin_sizeDotState(instance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_dislotwin_sizePostResults(instance)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_TITANMOD_ID)
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_titanmod_sizeState(instance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_titanmod_sizeState(instance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_titanmod_sizeState(instance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_titanmod_sizeState(instance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_titanmod_sizeState(instance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_titanmod_sizeState(instance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_titanmod_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_titanmod_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_titanmod_sizeDotState(instance)))
|
2013-11-27 13:34:05 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_titanmod_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_titanmod_sizeDotState(instance)))
|
2013-11-27 13:34:05 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_titanmod_sizeDotState(instance)))
|
2013-11-27 13:34:05 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_titanmod_sizeDotState(instance)))
|
2013-11-27 13:34:05 +05:30
|
|
|
enddo
|
|
|
|
endif
|
2014-03-09 02:20:31 +05:30
|
|
|
constitutive_state0(g,i,e)%p = constitutive_titanmod_stateInit(instance,material_phase(g,i,e))
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_titanmod_aTolState(instance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_titanmod_sizeState(instance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_titanmod_sizeDotState(instance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_titanmod_sizePostResults(instance)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONLOCAL_ID)
|
2013-05-24 19:13:44 +05:30
|
|
|
nonlocalConstitutionPresent = .true.
|
2013-02-04 20:04:01 +05:30
|
|
|
if(myNgrains/=1_pInt) call IO_error(252_pInt, e,i,g)
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_nonlocal_sizeState(instance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_nonlocal_sizeState(instance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_nonlocal_sizeState(instance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_nonlocal_sizeState(instance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_nonlocal_sizeState(instance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_nonlocal_sizeState(instance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_nonlocal_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_nonlocal_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(instance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_nonlocal_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
2014-02-28 15:48:40 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_nonlocal_sizeDotState(instance)))
|
2013-01-16 15:44:57 +05:30
|
|
|
enddo
|
|
|
|
endif
|
2014-02-28 15:48:40 +05:30
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_nonlocal_aTolState(instance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_nonlocal_sizeState(instance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_nonlocal_sizeDotState(instance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_nonlocal_sizePostResults(instance)
|
2013-01-16 15:44:57 +05:30
|
|
|
end select
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
2013-05-24 19:13:44 +05:30
|
|
|
if (nonlocalConstitutionPresent) &
|
|
|
|
call constitutive_nonlocal_stateInit(constitutive_state0(1,1:iMax,1:eMax))
|
2013-01-16 15:44:57 +05:30
|
|
|
do e = 1_pInt,mesh_NcpElems ! loop over elements
|
|
|
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
|
|
|
forall(i = 1_pInt:FE_Nips(FE_geomtype(mesh_element(2,e))), g = 1_pInt:myNgrains)
|
|
|
|
constitutive_partionedState0(g,i,e)%p = constitutive_state0(g,i,e)%p
|
|
|
|
constitutive_state(g,i,e)%p = constitutive_state0(g,i,e)%p ! need to be defined for first call of constitutive_microstructure in crystallite_init
|
|
|
|
endforall
|
|
|
|
enddo
|
2014-03-12 13:03:51 +05:30
|
|
|
#ifdef HDF
|
2014-03-26 14:11:45 +05:30
|
|
|
call HDF5_mappingConstitutive(mappingConstitutive)
|
2014-03-12 13:03:51 +05:30
|
|
|
#endif
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write out state size file
|
2013-09-18 19:37:55 +05:30
|
|
|
call IO_write_jobIntFile(777,'sizeStateConst', size(constitutive_sizeState))
|
2013-01-16 15:44:57 +05:30
|
|
|
write (777,rec=1) constitutive_sizeState
|
|
|
|
close(777)
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! report
|
|
|
|
constitutive_maxSizeState = maxval(constitutive_sizeState)
|
|
|
|
constitutive_maxSizeDotState = maxval(constitutive_sizeDotState)
|
|
|
|
constitutive_maxSizePostResults = maxval(constitutive_sizePostResults)
|
|
|
|
|
|
|
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) then
|
2013-11-27 13:34:05 +05:30
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_state0: ', shape(constitutive_state0)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_partionedState0: ', shape(constitutive_partionedState0)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_subState0: ', shape(constitutive_subState0)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_state: ', shape(constitutive_state)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_aTolState: ', shape(constitutive_aTolState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_dotState: ', shape(constitutive_dotState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_deltaState: ', shape(constitutive_deltaState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeState: ', shape(constitutive_sizeState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeDotState: ', shape(constitutive_sizeDotState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x),/)') 'constitutive_sizePostResults: ', shape(constitutive_sizePostResults)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'maxSizeState: ', constitutive_maxSizeState
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'maxSizeDotState: ', constitutive_maxSizeDotState
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'maxSizePostResults: ', constitutive_maxSizePostResults
|
2013-01-16 15:44:57 +05:30
|
|
|
endif
|
|
|
|
flush(6)
|
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_init
|
2009-03-06 15:32:36 +05:30
|
|
|
|
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief returns the homogenize elasticity matrix
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-09-19 13:16:01 +05:30
|
|
|
pure function constitutive_homogenizedC(ipc,ip,el)
|
2013-01-16 15:44:57 +05:30
|
|
|
use material, only: &
|
|
|
|
phase_plasticity, &
|
2013-11-27 13:34:05 +05:30
|
|
|
material_phase, &
|
|
|
|
PLASTICITY_TITANMOD_ID, &
|
2014-03-09 02:20:31 +05:30
|
|
|
PLASTICITY_DISLOTWIN_ID
|
2013-10-16 18:34:59 +05:30
|
|
|
use constitutive_dislotwin, only: &
|
|
|
|
constitutive_dislotwin_homogenizedC
|
2013-11-27 13:34:05 +05:30
|
|
|
use constitutive_titanmod, only: &
|
|
|
|
constitutive_titanmod_homogenizedC
|
2014-03-09 02:20:31 +05:30
|
|
|
use lattice, only: &
|
|
|
|
lattice_C66
|
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
implicit none
|
|
|
|
real(pReal), dimension(6,6) :: constitutive_homogenizedC
|
2013-01-16 15:44:57 +05:30
|
|
|
integer(pInt), intent(in) :: &
|
2013-09-19 13:16:01 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2013-09-19 13:16:01 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2009-08-11 22:01:57 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_DISLOTWIN_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_homogenizedC = constitutive_dislotwin_homogenizedC(constitutive_state(ipc,ip,el), &
|
|
|
|
ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_TITANMOD_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_homogenizedC = constitutive_titanmod_homogenizedC(constitutive_state(ipc,ip,el), &
|
|
|
|
ipc,ip,el)
|
2014-03-09 02:20:31 +05:30
|
|
|
case default
|
|
|
|
constitutive_homogenizedC = lattice_C66(1:6,1:6,material_phase(ipc,ip,el))
|
2009-08-11 22:01:57 +05:30
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
end select
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end function constitutive_homogenizedC
|
|
|
|
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief calls microstructure function of the different constitutive models
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-10-16 18:34:59 +05:30
|
|
|
subroutine constitutive_microstructure(temperature, Fe, Fp, ipc, ip, el)
|
2013-01-16 15:44:57 +05:30
|
|
|
use material, only: &
|
|
|
|
phase_plasticity, &
|
2013-11-27 13:34:05 +05:30
|
|
|
material_phase, &
|
|
|
|
PLASTICITY_DISLOTWIN_ID, &
|
|
|
|
PLASTICITY_TITANMOD_ID, &
|
|
|
|
PLASTICITY_NONLOCAL_ID
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_titanmod, only: &
|
|
|
|
constitutive_titanmod_microstructure
|
|
|
|
use constitutive_dislotwin, only: &
|
|
|
|
constitutive_dislotwin_microstructure
|
|
|
|
use constitutive_nonlocal, only: &
|
|
|
|
constitutive_nonlocal_microstructure
|
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
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: &
|
2013-10-14 16:24:45 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in) :: &
|
2013-10-16 18:34:59 +05:30
|
|
|
temperature
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: &
|
|
|
|
Fe, & !< elastic deformation gradient
|
|
|
|
Fp !< plastic deformation gradient
|
|
|
|
|
2013-09-19 13:16:01 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2013-11-27 13:34:05 +05:30
|
|
|
|
|
|
|
case (PLASTICITY_DISLOTWIN_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_dislotwin_microstructure(temperature,constitutive_state(ipc,ip,el), &
|
|
|
|
ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_TITANMOD_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_titanmod_microstructure(temperature,constitutive_state(ipc,ip,el), &
|
|
|
|
ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONLOCAL_ID)
|
2013-10-16 18:34:59 +05:30
|
|
|
call constitutive_nonlocal_microstructure(constitutive_state,Fe,Fp,ipc,ip,el)
|
2013-10-14 16:24:45 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
end select
|
|
|
|
|
|
|
|
end subroutine constitutive_microstructure
|
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
|
|
|
|
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-09-19 13:16:01 +05:30
|
|
|
!> @brief contains the constitutive equation for calculating the velocity gradient
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-10-16 18:34:59 +05:30
|
|
|
subroutine constitutive_LpAndItsTangent(Lp, dLp_dTstar, Tstar_v, temperature, ipc, ip, el)
|
|
|
|
use math, only: &
|
|
|
|
math_identity2nd
|
2013-01-16 15:44:57 +05:30
|
|
|
use material, only: &
|
|
|
|
phase_plasticity, &
|
2013-11-27 13:34:05 +05:30
|
|
|
material_phase, &
|
|
|
|
PLASTICITY_NONE_ID, &
|
|
|
|
PLASTICITY_J2_ID, &
|
|
|
|
PLASTICITY_PHENOPOWERLAW_ID, &
|
|
|
|
PLASTICITY_DISLOTWIN_ID, &
|
|
|
|
PLASTICITY_TITANMOD_ID, &
|
|
|
|
PLASTICITY_NONLOCAL_ID
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_j2, only: &
|
|
|
|
constitutive_j2_LpAndItsTangent
|
|
|
|
use constitutive_phenopowerlaw, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_phenopowerlaw_LpAndItsTangent
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_dislotwin, only: &
|
|
|
|
constitutive_dislotwin_LpAndItsTangent
|
2013-11-27 13:34:05 +05:30
|
|
|
use constitutive_titanmod, only: &
|
|
|
|
constitutive_titanmod_LpAndItsTangent
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_nonlocal, only: &
|
|
|
|
constitutive_nonlocal_LpAndItsTangent
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: &
|
2013-10-14 16:24:45 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
Temperature
|
|
|
|
real(pReal), intent(in), dimension(6) :: &
|
|
|
|
Tstar_v !< 2nd Piola-Kirchhoff stress
|
|
|
|
real(pReal), intent(out), dimension(3,3) :: &
|
|
|
|
Lp !< plastic velocity gradient
|
|
|
|
real(pReal), intent(out), dimension(9,9) :: &
|
|
|
|
dLp_dTstar !< derivative of Lp with respect to Tstar (4th-order tensor)
|
|
|
|
|
2013-09-19 13:16:01 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONE_ID)
|
2013-10-16 18:34:59 +05:30
|
|
|
Lp = 0.0_pReal
|
|
|
|
dLp_dTstar = math_identity2nd(9)
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_J2_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_j2_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v, &
|
|
|
|
constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_PHENOPOWERLAW_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_phenopowerlaw_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v, &
|
|
|
|
constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_DISLOTWIN_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_dislotwin_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v, &
|
|
|
|
temperature,constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_TITANMOD_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_titanmod_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v, &
|
|
|
|
temperature,constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONLOCAL_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_nonlocal_LpAndItsTangent(Lp, dLp_dTstar, Tstar_v, &
|
|
|
|
temperature, constitutive_state(ipc,ip,el), ipc,ip,el)
|
2013-01-16 15:44:57 +05:30
|
|
|
end select
|
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_LpAndItsTangent
|
2009-03-06 15:32:36 +05:30
|
|
|
|
|
|
|
|
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
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief returns the 2nd Piola-Kirchhoff stress tensor and its tangent with respect to
|
2013-10-14 16:24:45 +05:30
|
|
|
!> the elastic deformation gradient depending on the selected elastic law (so far no case switch
|
|
|
|
!! because only hooke is implemented
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-09-19 13:16:01 +05:30
|
|
|
pure subroutine constitutive_TandItsTangent(T, dT_dFe, Fe, ipc, ip, el)
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: &
|
2013-10-14 16:24:45 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: &
|
|
|
|
Fe !< elastic deformation gradient
|
|
|
|
real(pReal), intent(out), dimension(3,3) :: &
|
|
|
|
T !< 2nd Piola-Kirchhoff stress tensor
|
|
|
|
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
|
|
|
dT_dFe !< derivative of 2nd P-K stress with respect to elastic deformation gradient
|
|
|
|
|
2013-10-14 16:24:45 +05:30
|
|
|
call constitutive_hooke_TandItsTangent(T, dT_dFe, Fe, ipc, ip, el)
|
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_TandItsTangent
|
2012-03-15 15:21:33 +05:30
|
|
|
|
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief returns the 2nd Piola-Kirchhoff stress tensor and its tangent with respect to
|
2013-10-14 20:05:41 +05:30
|
|
|
!> the elastic deformation gradient using hookes law
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-09-19 13:16:01 +05:30
|
|
|
pure subroutine constitutive_hooke_TandItsTangent(T, dT_dFe, Fe, ipc, ip, el)
|
2013-01-08 16:39:20 +05:30
|
|
|
use math, only : &
|
2014-01-22 14:08:13 +05:30
|
|
|
math_mul3x3, &
|
2013-01-08 16:39:20 +05:30
|
|
|
math_mul33x33, &
|
2013-01-09 03:24:25 +05:30
|
|
|
math_mul3333xx33, &
|
2013-01-08 16:39:20 +05:30
|
|
|
math_Mandel66to3333, &
|
2013-01-09 03:24:25 +05:30
|
|
|
math_transpose33, &
|
2013-09-19 13:16:01 +05:30
|
|
|
MATH_I3
|
2012-11-07 21:13:29 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: &
|
2013-10-14 16:24:45 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: &
|
|
|
|
Fe !< elastic deformation gradient
|
|
|
|
real(pReal), intent(out), dimension(3,3) :: &
|
|
|
|
T !< 2nd Piola-Kirchhoff stress tensor
|
|
|
|
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
|
|
|
dT_dFe !< dT/dFe
|
|
|
|
|
2014-01-22 14:08:13 +05:30
|
|
|
integer(pInt) :: i, j, k, l
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), dimension(3,3) :: FeT
|
|
|
|
real(pReal), dimension(3,3,3,3) :: C
|
2012-03-15 15:21:33 +05:30
|
|
|
|
|
|
|
|
2013-09-19 13:16:01 +05:30
|
|
|
C = math_Mandel66to3333(constitutive_homogenizedC(ipc,ip,el))
|
2012-03-15 15:21:33 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
FeT = math_transpose33(Fe)
|
2014-01-22 14:08:13 +05:30
|
|
|
T = 0.5_pReal * math_mul3333xx33(C, math_mul33x33(FeT,Fe)-MATH_I3)
|
2012-03-15 15:21:33 +05:30
|
|
|
|
2014-01-22 14:08:13 +05:30
|
|
|
dT_dFe = 0.0_pReal
|
|
|
|
forall (i=1_pInt:3_pInt, j=1_pInt:3_pInt, k=1_pInt:3_pInt, l=1_pInt:3_pInt) &
|
|
|
|
dT_dFe(i,j,k,l) = math_mul3x3(C(i,j,l,1:3),Fe(k,1:3)) ! dT*_ij/dFe_kl
|
2012-03-15 15:21:33 +05:30
|
|
|
|
|
|
|
end subroutine constitutive_hooke_TandItsTangent
|
|
|
|
|
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2014-03-13 12:13:49 +05:30
|
|
|
subroutine constitutive_collectDotState(Tstar_v, FeArray, FpArray, Temperature, subdt, subfracArray,&
|
|
|
|
ipc, ip, el)
|
2013-01-16 15:44:57 +05:30
|
|
|
use prec, only: &
|
|
|
|
pLongInt
|
|
|
|
use debug, only: &
|
|
|
|
debug_cumDotStateCalls, &
|
|
|
|
debug_cumDotStateTicks, &
|
|
|
|
debug_level, &
|
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_NcpElems, &
|
2013-05-08 14:53:47 +05:30
|
|
|
mesh_maxNips
|
2013-01-16 15:44:57 +05:30
|
|
|
use material, only: &
|
|
|
|
phase_plasticity, &
|
|
|
|
material_phase, &
|
2013-11-27 13:34:05 +05:30
|
|
|
homogenization_maxNgrains, &
|
|
|
|
PLASTICITY_NONE_ID, &
|
|
|
|
PLASTICITY_J2_ID, &
|
|
|
|
PLASTICITY_PHENOPOWERLAW_ID, &
|
|
|
|
PLASTICITY_DISLOTWIN_ID, &
|
|
|
|
PLASTICITY_TITANMOD_ID, &
|
|
|
|
PLASTICITY_NONLOCAL_ID
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_j2, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_j2_dotState
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_phenopowerlaw, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_phenopowerlaw_dotState
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_dislotwin, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_dislotwin_dotState
|
|
|
|
use constitutive_titanmod, only: &
|
|
|
|
constitutive_titanmod_dotState
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_nonlocal, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_nonlocal_dotState
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: &
|
2013-10-14 16:24:45 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
Temperature, &
|
|
|
|
subdt !< timestep
|
|
|
|
real(pReal), intent(in), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: &
|
2014-03-13 12:13:49 +05:30
|
|
|
subfracArray !< subfraction of timestep
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: &
|
2014-03-13 12:13:49 +05:30
|
|
|
FeArray, & !< elastic deformation gradient
|
|
|
|
FpArray !< plastic deformation gradient
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(6) :: &
|
|
|
|
Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
|
|
|
|
integer(pLongInt) :: &
|
|
|
|
tick, tock, &
|
|
|
|
tickrate, &
|
|
|
|
maxticks
|
2012-07-03 16:46:38 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) &
|
|
|
|
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
|
2009-12-15 13:50:31 +05:30
|
|
|
|
2013-09-19 13:16:01 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONE_ID)
|
2013-10-14 16:24:45 +05:30
|
|
|
constitutive_dotState(ipc,ip,el)%p = 0.0_pReal !ToDo: needed or will it remain zero anyway?
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_J2_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_j2_dotState(Tstar_v,&
|
|
|
|
constitutive_state(ipc,ip,el), ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_PHENOPOWERLAW_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_phenopowerlaw_dotState(Tstar_v,&
|
|
|
|
constitutive_state(ipc,ip,el), ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_TITANMOD_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_titanmod_dotState(Tstar_v,Temperature,&
|
|
|
|
constitutive_state(ipc,ip,el), ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_DISLOTWIN_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_dislotwin_dotState(Tstar_v,Temperature,&
|
|
|
|
constitutive_state(ipc,ip,el), ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONLOCAL_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_nonlocal_dotState(Tstar_v, FeArray, FpArray, &
|
|
|
|
Temperature, constitutive_state, constitutive_state0, subdt, &
|
|
|
|
subfracArray, ipc, ip, el)
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
end select
|
|
|
|
|
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
|
|
|
call system_clock(count=tock,count_rate=tickrate,count_max=maxticks)
|
|
|
|
!$OMP CRITICAL (debugTimingDotState)
|
|
|
|
debug_cumDotStateCalls = debug_cumDotStateCalls + 1_pInt
|
|
|
|
debug_cumDotStateTicks = debug_cumDotStateTicks + tock-tick
|
|
|
|
!$OMP FLUSH (debug_cumDotStateTicks)
|
|
|
|
if (tock < tick) debug_cumDotStateTicks = debug_cumDotStateTicks + maxticks
|
|
|
|
!$OMP END CRITICAL (debugTimingDotState)
|
|
|
|
endif
|
2009-12-15 13:50:31 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_collectDotState
|
2009-03-06 15:32:36 +05:30
|
|
|
|
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief contains the constitutive equation for calculating the incremental change of
|
|
|
|
!> microstructure based on the current stress and state
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-10-16 18:34:59 +05:30
|
|
|
subroutine constitutive_collectDeltaState(Tstar_v, ipc, ip, el)
|
2013-01-16 15:44:57 +05:30
|
|
|
use prec, only: &
|
|
|
|
pLongInt
|
|
|
|
use debug, only: &
|
|
|
|
debug_cumDeltaStateCalls, &
|
|
|
|
debug_cumDeltaStateTicks, &
|
|
|
|
debug_level, &
|
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
|
|
|
use material, only: &
|
|
|
|
phase_plasticity, &
|
2013-11-27 13:34:05 +05:30
|
|
|
material_phase, &
|
|
|
|
PLASTICITY_NONLOCAL_ID
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_nonlocal, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_nonlocal_deltaState
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: &
|
2013-10-14 16:24:45 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(6) :: &
|
|
|
|
Tstar_v !< 2nd Piola-Kirchhoff stress
|
|
|
|
integer(pLongInt) :: &
|
|
|
|
tick, tock, &
|
|
|
|
tickrate, &
|
|
|
|
maxticks
|
|
|
|
|
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) &
|
|
|
|
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
|
|
|
|
|
2013-09-19 13:16:01 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2012-05-16 20:13:26 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONLOCAL_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
call constitutive_nonlocal_deltaState(constitutive_deltaState(ipc,ip,el),&
|
|
|
|
constitutive_state(ipc,ip,el), Tstar_v,ipc,ip,el)
|
2013-10-14 16:24:45 +05:30
|
|
|
|
|
|
|
case default
|
|
|
|
constitutive_deltaState(ipc,ip,el)%p = 0.0_pReal !ToDo: needed or will it remain zero anyway?
|
2012-05-16 20:13:26 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
end select
|
2012-05-16 20:13:26 +05:30
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
|
|
|
call system_clock(count=tock,count_rate=tickrate,count_max=maxticks)
|
|
|
|
!$OMP CRITICAL (debugTimingDeltaState)
|
|
|
|
debug_cumDeltaStateCalls = debug_cumDeltaStateCalls + 1_pInt
|
|
|
|
debug_cumDeltaStateTicks = debug_cumDeltaStateTicks + tock-tick
|
|
|
|
!$OMP FLUSH (debug_cumDeltaStateTicks)
|
|
|
|
if (tock < tick) debug_cumDeltaStateTicks = debug_cumDeltaStateTicks + maxticks
|
|
|
|
!$OMP END CRITICAL (debugTimingDeltaState)
|
|
|
|
endif
|
2012-05-16 20:13:26 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_collectDeltaState
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
|
2013-01-16 15:44:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief returns array of constitutive results
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2014-03-13 12:13:49 +05:30
|
|
|
function constitutive_postResults(Tstar_v, FeArray, temperature, ipc, ip, el)
|
2013-01-16 15:44:57 +05:30
|
|
|
use mesh, only: &
|
|
|
|
mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: &
|
|
|
|
phase_plasticity, &
|
|
|
|
material_phase, &
|
2013-11-27 13:34:05 +05:30
|
|
|
homogenization_maxNgrains, &
|
|
|
|
PLASTICITY_NONE_ID, &
|
|
|
|
PLASTICITY_J2_ID, &
|
|
|
|
PLASTICITY_PHENOPOWERLAW_ID, &
|
|
|
|
PLASTICITY_DISLOTWIN_ID, &
|
|
|
|
PLASTICITY_TITANMOD_ID, &
|
|
|
|
PLASTICITY_NONLOCAL_ID
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_j2, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_j2_postResults
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_phenopowerlaw, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_phenopowerlaw_postResults
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_dislotwin, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_dislotwin_postResults
|
|
|
|
use constitutive_titanmod, only: &
|
|
|
|
constitutive_titanmod_postResults
|
2013-01-16 15:44:57 +05:30
|
|
|
use constitutive_nonlocal, only: &
|
2013-11-27 13:34:05 +05:30
|
|
|
constitutive_nonlocal_postResults
|
2013-01-16 15:44:57 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: &
|
2013-10-14 16:24:45 +05:30
|
|
|
ipc, & !< grain number
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2013-09-19 13:16:01 +05:30
|
|
|
real(pReal), dimension(constitutive_sizePostResults(ipc,ip,el)) :: &
|
2013-01-16 15:44:57 +05:30
|
|
|
constitutive_postResults
|
|
|
|
real(pReal), intent(in) :: &
|
2013-10-16 18:34:59 +05:30
|
|
|
temperature
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: &
|
2014-03-13 12:13:49 +05:30
|
|
|
FeArray !< elastic deformation gradient
|
2013-01-16 15:44:57 +05:30
|
|
|
real(pReal), intent(in), dimension(6) :: &
|
|
|
|
Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
|
|
|
|
|
|
|
|
constitutive_postResults = 0.0_pReal
|
|
|
|
|
2013-09-19 13:16:01 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONE_ID)
|
2013-01-16 15:44:57 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_TITANMOD_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_postResults = constitutive_titanmod_postResults(&
|
|
|
|
constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_J2_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_postResults = constitutive_j2_postResults(Tstar_v,&
|
|
|
|
constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_PHENOPOWERLAW_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_postResults = constitutive_phenopowerlaw_postResults(Tstar_v,&
|
|
|
|
constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_DISLOTWIN_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_postResults = constitutive_dislotwin_postResults(Tstar_v,Temperature,&
|
|
|
|
constitutive_state(ipc,ip,el),ipc,ip,el)
|
2013-11-27 13:34:05 +05:30
|
|
|
case (PLASTICITY_NONLOCAL_ID)
|
2014-03-13 12:13:49 +05:30
|
|
|
constitutive_postResults = constitutive_nonlocal_postResults(Tstar_v, FeArray, &
|
|
|
|
constitutive_state, constitutive_dotstate(ipc,ip,el), ipc, ip, el)
|
2013-01-16 15:44:57 +05:30
|
|
|
end select
|
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
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end function constitutive_postResults
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-14 21:46:11 +05:30
|
|
|
|
2013-02-11 16:13:45 +05:30
|
|
|
end module constitutive
|