2011-04-07 12:50:28 +05:30
|
|
|
! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! This file is part of DAMASK,
|
2011-04-07 12:50:28 +05:30
|
|
|
! the Düsseldorf Advanced MAterial Simulation Kit.
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! DAMASK is free software: you can redistribute it and/or modify
|
|
|
|
! it under the terms of the GNU General Public License as published by
|
|
|
|
! the Free Software Foundation, either version 3 of the License, or
|
|
|
|
! (at your option) any later version.
|
|
|
|
!
|
|
|
|
! DAMASK is distributed in the hope that it will be useful,
|
|
|
|
! but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
! GNU General Public License for more details.
|
|
|
|
!
|
|
|
|
! You should have received a copy of the GNU General Public License
|
|
|
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
|
|
|
!
|
|
|
|
!##############################################################
|
2009-08-31 20:39:15 +05:30
|
|
|
!* $Id$
|
2009-03-06 15:43:08 +05:30
|
|
|
!*****************************************************
|
2010-10-26 18:46:37 +05:30
|
|
|
!* Module: CONSTITUTIVE_J2 *
|
2009-03-06 15:43:08 +05:30
|
|
|
!*****************************************************
|
|
|
|
!* contains: *
|
|
|
|
!* - constitutive equations *
|
|
|
|
!* - parameters definition *
|
|
|
|
!*****************************************************
|
|
|
|
|
2010-10-26 18:46:37 +05:30
|
|
|
! [Alu]
|
2012-03-12 20:13:19 +05:30
|
|
|
! plasticity j2
|
2010-10-26 18:46:37 +05:30
|
|
|
! (output) flowstress
|
|
|
|
! (output) strainrate
|
|
|
|
! c11 110.9e9 # (3 C11 + 2 C12 + 2 C44) / 5 ... with C44 = C11-C12 !!
|
|
|
|
! c12 58.34e9 # (1 C11 + 4 C12 - 1 C44) / 5
|
|
|
|
! taylorfactor 3
|
|
|
|
! tau0 31e6
|
|
|
|
! gdot0 0.001
|
|
|
|
! n 20
|
|
|
|
! h0 75e6
|
|
|
|
! tausat 63e6
|
2011-11-23 20:18:39 +05:30
|
|
|
! a 2.25
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
module constitutive_j2
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
use prec, only: pReal,pInt
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2009-03-06 15:43:08 +05:30
|
|
|
implicit none
|
2012-03-09 01:55:28 +05:30
|
|
|
private
|
|
|
|
character (len=*), parameter, public :: constitutive_j2_label = 'j2'
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable, public :: &
|
|
|
|
constitutive_j2_sizeDotState, &
|
|
|
|
constitutive_j2_sizeState, &
|
|
|
|
constitutive_j2_sizePostResults
|
|
|
|
|
|
|
|
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
|
|
constitutive_j2_sizePostResult ! size of each post result output
|
|
|
|
|
|
|
|
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
|
|
constitutive_j2_output ! name of each post result output
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
integer(pInt), dimension(:), allocatable, private :: &
|
|
|
|
constitutive_j2_Noutput
|
|
|
|
|
|
|
|
real(pReal), dimension(:), allocatable, private :: &
|
2012-04-11 19:31:02 +05:30
|
|
|
constitutive_j2_C11, &
|
|
|
|
constitutive_j2_C12, &
|
|
|
|
!* Visco-plastic constitutive_j2 parameters
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_fTaylor, &
|
|
|
|
constitutive_j2_tau0, &
|
|
|
|
constitutive_j2_gdot0, &
|
|
|
|
constitutive_j2_n, &
|
2012-04-11 19:31:02 +05:30
|
|
|
!* h0 as function of h0 = A + B log (gammadot)
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_h0, &
|
2012-04-11 19:31:02 +05:30
|
|
|
constitutive_j2_h0_slopeLnRate, &
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_tausat, &
|
|
|
|
constitutive_j2_a, &
|
2012-04-11 19:31:02 +05:30
|
|
|
constitutive_j2_aTolResistance, &
|
|
|
|
!* Parameters of normalized strain rate vs. stress function:
|
|
|
|
!* tausat += (asinh((gammadot / SinhFitA)**(1 / SinhFitD)))**(1 / SinhFitC) / (SinhFitB * (gammadot / gammadot0)**(1/n))
|
|
|
|
constitutive_j2_tausat_SinhFitA, &
|
|
|
|
constitutive_j2_tausat_SinhFitB, &
|
|
|
|
constitutive_j2_tausat_SinhFitC, &
|
|
|
|
constitutive_j2_tausat_SinhFitD
|
|
|
|
|
|
|
|
real(pReal), dimension(:,:,:), allocatable, private :: &
|
|
|
|
constitutive_j2_Cslip_66
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
public :: constitutive_j2_init, &
|
|
|
|
constitutive_j2_stateInit, &
|
|
|
|
constitutive_j2_aTolState, &
|
|
|
|
constitutive_j2_homogenizedC, &
|
|
|
|
constitutive_j2_microstructure, &
|
|
|
|
constitutive_j2_LpAndItsTangent, &
|
|
|
|
constitutive_j2_dotState, &
|
2012-05-16 20:13:26 +05:30
|
|
|
constitutive_j2_deltaState, &
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_dotTemperature, &
|
|
|
|
constitutive_j2_postResults
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
subroutine constitutive_j2_init(myFile)
|
2009-03-06 15:43:08 +05:30
|
|
|
!**************************************
|
|
|
|
!* Module initialization *
|
|
|
|
!**************************************
|
2012-02-21 21:30:00 +05:30
|
|
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2012-04-11 19:31:02 +05:30
|
|
|
use math, only: &
|
|
|
|
math_Mandel3333to66, &
|
|
|
|
math_Voigt66to3333
|
|
|
|
use IO, only: &
|
|
|
|
IO_lc, &
|
|
|
|
IO_getTag, &
|
|
|
|
IO_isBlank, &
|
|
|
|
IO_stringPos, &
|
|
|
|
IO_stringValue, &
|
|
|
|
IO_floatValue, &
|
|
|
|
IO_error
|
2009-03-06 15:43:08 +05:30
|
|
|
use material
|
2012-04-11 19:31:02 +05:30
|
|
|
use debug, only: &
|
2012-07-05 15:24:50 +05:30
|
|
|
debug_level, &
|
2012-04-11 19:31:02 +05:30
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
2012-03-09 01:55:28 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: myFile
|
|
|
|
|
2012-02-21 21:30:00 +05:30
|
|
|
integer(pInt), parameter :: maxNchunks = 7_pInt
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2012-02-21 21:30:00 +05:30
|
|
|
integer(pInt), dimension(1_pInt+2_pInt*maxNchunks) :: positions
|
2012-07-17 23:06:24 +05:30
|
|
|
integer(pInt) :: section = 0_pInt, maxNinstance, i,j,k,o, mySize
|
2012-03-09 01:55:28 +05:30
|
|
|
character(len=64) :: tag
|
2013-01-09 03:41:59 +05:30
|
|
|
character(len=1024) :: line = '' ! to start initialized
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2013-01-09 03:41:59 +05:30
|
|
|
write(6,*)
|
|
|
|
write(6,*) '<<<+- constitutive_',trim(constitutive_j2_label),' init -+>>>'
|
|
|
|
write(6,*) '$Id$'
|
2012-02-01 00:48:55 +05:30
|
|
|
#include "compilation_info.f90"
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
maxNinstance = int(count(phase_plasticity == constitutive_j2_label),pInt)
|
2012-02-21 21:30:00 +05:30
|
|
|
if (maxNinstance == 0_pInt) return
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) then
|
2013-01-09 03:41:59 +05:30
|
|
|
write(6,'(a16,1x,i5)') '# instances:',maxNinstance
|
|
|
|
write(6,*)
|
2011-03-21 16:01:17 +05:30
|
|
|
endif
|
2009-10-16 01:32:52 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
allocate(constitutive_j2_sizeDotState(maxNinstance))
|
|
|
|
constitutive_j2_sizeDotState = 0_pInt
|
|
|
|
allocate(constitutive_j2_sizeState(maxNinstance))
|
|
|
|
constitutive_j2_sizeState = 0_pInt
|
|
|
|
allocate(constitutive_j2_sizePostResults(maxNinstance))
|
|
|
|
constitutive_j2_sizePostResults = 0_pInt
|
|
|
|
allocate(constitutive_j2_sizePostResult(maxval(phase_Noutput), maxNinstance))
|
|
|
|
constitutive_j2_sizePostResult = 0_pInt
|
|
|
|
allocate(constitutive_j2_output(maxval(phase_Noutput), maxNinstance))
|
|
|
|
constitutive_j2_output = ''
|
|
|
|
allocate(constitutive_j2_Noutput(maxNinstance))
|
|
|
|
constitutive_j2_Noutput = 0_pInt
|
|
|
|
allocate(constitutive_j2_C11(maxNinstance))
|
|
|
|
constitutive_j2_C11 = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_C12(maxNinstance))
|
|
|
|
constitutive_j2_C12 = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_Cslip_66(6,6,maxNinstance))
|
|
|
|
constitutive_j2_Cslip_66 = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_fTaylor(maxNinstance))
|
|
|
|
constitutive_j2_fTaylor = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_tau0(maxNinstance))
|
|
|
|
constitutive_j2_tau0 = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_gdot0(maxNinstance))
|
|
|
|
constitutive_j2_gdot0 = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_n(maxNinstance))
|
|
|
|
constitutive_j2_n = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_h0(maxNinstance))
|
|
|
|
constitutive_j2_h0 = 0.0_pReal
|
2012-04-20 17:48:38 +05:30
|
|
|
allocate(constitutive_j2_h0_slopeLnRate(maxNinstance))
|
|
|
|
constitutive_j2_h0_slopeLnRate = 0.0_pReal
|
2012-03-09 01:55:28 +05:30
|
|
|
allocate(constitutive_j2_tausat(maxNinstance))
|
|
|
|
constitutive_j2_tausat = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_a(maxNinstance))
|
|
|
|
constitutive_j2_a = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_aTolResistance(maxNinstance))
|
|
|
|
constitutive_j2_aTolResistance = 0.0_pReal
|
2012-04-11 19:42:30 +05:30
|
|
|
allocate(constitutive_j2_tausat_SinhFitA(maxNinstance))
|
|
|
|
constitutive_j2_tausat_SinhFitA = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_tausat_SinhFitB(maxNinstance))
|
|
|
|
constitutive_j2_tausat_SinhFitB = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_tausat_SinhFitC(maxNinstance))
|
|
|
|
constitutive_j2_tausat_SinhFitC = 0.0_pReal
|
|
|
|
allocate(constitutive_j2_tausat_SinhFitD(maxNinstance))
|
|
|
|
constitutive_j2_tausat_SinhFitD = 0.0_pReal
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
rewind(myFile)
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-02-14 05:00:59 +05:30
|
|
|
do while (IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
2012-03-09 01:55:28 +05:30
|
|
|
read(myFile,'(a1024)',END=100) line
|
2009-03-06 15:43:08 +05:30
|
|
|
enddo
|
2012-02-14 05:00:59 +05:30
|
|
|
|
|
|
|
do ! read thru sections of phase part
|
2012-03-09 01:55:28 +05:30
|
|
|
read(myFile,'(a1024)',END=100) line
|
2012-02-14 05:00:59 +05:30
|
|
|
if (IO_isBlank(line)) cycle ! skip empty lines
|
|
|
|
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
|
|
|
if (IO_getTag(line,'[',']') /= '') then ! next section
|
|
|
|
section = section + 1_pInt ! advance section counter
|
|
|
|
cycle
|
2009-03-06 15:43:08 +05:30
|
|
|
endif
|
2012-03-12 19:39:37 +05:30
|
|
|
if (section > 0_pInt .and. phase_plasticity(section) == constitutive_j2_label) then ! one of my sections
|
2012-03-12 20:13:19 +05:30
|
|
|
i = phase_plasticityInstance(section) ! which instance of my plasticity is present phase
|
2009-03-06 15:43:08 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
2012-02-14 05:00:59 +05:30
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
|
2009-03-06 15:43:08 +05:30
|
|
|
select case(tag)
|
2012-03-15 14:55:15 +05:30
|
|
|
case ('plasticity','elasticity')
|
2012-02-14 14:52:37 +05:30
|
|
|
cycle
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('(output)')
|
2012-02-14 20:49:59 +05:30
|
|
|
constitutive_j2_Noutput(i) = constitutive_j2_Noutput(i) + 1_pInt
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_output(constitutive_j2_Noutput(i),i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('c11')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_C11(i) = IO_floatValue(line,positions,2_pInt)
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('c12')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_C12(i) = IO_floatValue(line,positions,2_pInt)
|
2009-06-23 16:09:29 +05:30
|
|
|
case ('tau0')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_tau0(i) = IO_floatValue(line,positions,2_pInt)
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('gdot0')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_gdot0(i) = IO_floatValue(line,positions,2_pInt)
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('n')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_n(i) = IO_floatValue(line,positions,2_pInt)
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('h0')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_h0(i) = IO_floatValue(line,positions,2_pInt)
|
2012-04-20 17:48:38 +05:30
|
|
|
case ('h0_slope','slopelnrate')
|
2012-04-11 19:31:02 +05:30
|
|
|
constitutive_j2_h0_slopeLnRate(i) = IO_floatValue(line,positions,2)
|
2009-07-22 21:37:19 +05:30
|
|
|
case ('tausat')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_tausat(i) = IO_floatValue(line,positions,2_pInt)
|
2012-04-11 19:31:02 +05:30
|
|
|
case ('tausat_sinhfita')
|
|
|
|
constitutive_j2_tausat_SinhFitA(i) = IO_floatValue(line,positions,2)
|
|
|
|
case ('tausat_sinhfitb')
|
|
|
|
constitutive_j2_tausat_SinhFitB(i) = IO_floatValue(line,positions,2)
|
|
|
|
case ('tausat_sinhfitc')
|
|
|
|
constitutive_j2_tausat_SinhFitC(i) = IO_floatValue(line,positions,2)
|
|
|
|
case ('tausat_sinhfitd')
|
|
|
|
constitutive_j2_tausat_SinhFitD(i) = IO_floatValue(line,positions,2)
|
2011-11-23 20:18:39 +05:30
|
|
|
case ('a', 'w0')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_a(i) = IO_floatValue(line,positions,2_pInt)
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('taylorfactor')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_fTaylor(i) = IO_floatValue(line,positions,2_pInt)
|
2010-10-26 18:46:37 +05:30
|
|
|
case ('atol_resistance')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_aTolResistance(i) = IO_floatValue(line,positions,2_pInt)
|
2012-02-13 23:11:27 +05:30
|
|
|
case default
|
2012-07-17 23:06:24 +05:30
|
|
|
call IO_error(210_pInt,ext_msg=tag//' ('//constitutive_j2_label//')')
|
2009-03-06 15:43:08 +05:30
|
|
|
end select
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
2012-02-21 21:30:00 +05:30
|
|
|
100 do i = 1_pInt,maxNinstance ! sanity checks
|
2012-07-17 23:06:24 +05:30
|
|
|
if (constitutive_j2_tau0(i) < 0.0_pReal) call IO_error(211_pInt,ext_msg='tau0 (' &
|
|
|
|
//constitutive_j2_label//')')
|
|
|
|
if (constitutive_j2_gdot0(i) <= 0.0_pReal) call IO_error(211_pInt,ext_msg='gdot0 (' &
|
|
|
|
//constitutive_j2_label//')')
|
|
|
|
if (constitutive_j2_n(i) <= 0.0_pReal) call IO_error(211_pInt,ext_msg='n (' &
|
|
|
|
//constitutive_j2_label//')')
|
|
|
|
if (constitutive_j2_tausat(i) <= 0.0_pReal) call IO_error(211_pInt,ext_msg='tausat (' &
|
|
|
|
//constitutive_j2_label//')')
|
|
|
|
if (constitutive_j2_a(i) <= 0.0_pReal) call IO_error(211_pInt,ext_msg='a (' &
|
|
|
|
//constitutive_j2_label//')')
|
|
|
|
if (constitutive_j2_fTaylor(i) <= 0.0_pReal) call IO_error(211_pInt,ext_msg='taylorfactor (' &
|
|
|
|
//constitutive_j2_label//')')
|
|
|
|
if (constitutive_j2_aTolResistance(i) <= 0.0_pReal) call IO_error(211_pInt,ext_msg='aTol_resistance (' &
|
|
|
|
//constitutive_j2_label//')')
|
2009-03-06 15:43:08 +05:30
|
|
|
enddo
|
|
|
|
|
2012-02-21 21:30:00 +05:30
|
|
|
do i = 1_pInt,maxNinstance
|
2012-07-17 23:06:24 +05:30
|
|
|
do o = 1_pInt,constitutive_j2_Noutput(i)
|
|
|
|
select case(constitutive_j2_output(o,i))
|
2010-10-26 18:46:37 +05:30
|
|
|
case('flowstress')
|
2012-02-13 23:11:27 +05:30
|
|
|
mySize = 1_pInt
|
2010-10-26 18:46:37 +05:30
|
|
|
case('strainrate')
|
2012-02-13 23:11:27 +05:30
|
|
|
mySize = 1_pInt
|
2010-10-26 18:46:37 +05:30
|
|
|
case default
|
2012-07-17 23:06:24 +05:30
|
|
|
call IO_error(212_pInt,ext_msg=constitutive_j2_output(o,i)//' ('//constitutive_j2_label//')')
|
2010-10-26 18:46:37 +05:30
|
|
|
end select
|
|
|
|
|
|
|
|
if (mySize > 0_pInt) then ! any meaningful output found
|
2012-08-29 21:46:10 +05:30
|
|
|
constitutive_j2_sizePostResult(o,i) = mySize
|
2010-10-26 18:46:37 +05:30
|
|
|
constitutive_j2_sizePostResults(i) = &
|
|
|
|
constitutive_j2_sizePostResults(i) + mySize
|
|
|
|
endif
|
2009-03-06 15:43:08 +05:30
|
|
|
enddo
|
|
|
|
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_sizeDotState(i) = 1_pInt
|
|
|
|
constitutive_j2_sizeState(i) = 1_pInt
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2012-02-21 21:30:00 +05:30
|
|
|
forall(k=1_pInt:3_pInt)
|
|
|
|
forall(j=1_pInt:3_pInt)
|
|
|
|
constitutive_j2_Cslip_66(k,j,i) = constitutive_j2_C12(i)
|
|
|
|
end forall
|
|
|
|
constitutive_j2_Cslip_66(k,k,i) = constitutive_j2_C11(i)
|
2012-02-13 23:11:27 +05:30
|
|
|
constitutive_j2_Cslip_66(k+3,k+3,i) = 0.5_pReal*(constitutive_j2_C11(i)-constitutive_j2_C12(i))
|
2009-03-06 15:43:08 +05:30
|
|
|
end forall
|
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
|
|
|
constitutive_j2_Cslip_66(1:6,1:6,i) = &
|
|
|
|
math_Mandel3333to66(math_Voigt66to3333(constitutive_j2_Cslip_66(1:6,1:6,i)))
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
enddo
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine constitutive_j2_init
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
|
|
|
!*********************************************************************
|
|
|
|
!* initial microstructural state *
|
|
|
|
!*********************************************************************
|
2009-06-23 16:09:29 +05:30
|
|
|
pure function constitutive_j2_stateInit(myInstance)
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: myInstance
|
|
|
|
real(pReal), dimension(1) :: constitutive_j2_stateInit
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_stateInit = constitutive_j2_tau0(myInstance)
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function constitutive_j2_stateInit
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
2009-09-18 21:07:14 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* relevant microstructural state *
|
|
|
|
!*********************************************************************
|
2010-10-26 18:46:37 +05:30
|
|
|
pure function constitutive_j2_aTolState(myInstance)
|
2009-09-18 21:07:14 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
|
|
|
!*** input variables
|
2012-03-12 20:13:19 +05:30
|
|
|
integer(pInt), intent(in) :: myInstance ! number specifying the current instance of the plasticity
|
2009-09-18 21:07:14 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
!*** output variables
|
|
|
|
real(pReal), dimension(constitutive_j2_sizeState(myInstance)) :: &
|
2012-03-12 20:13:19 +05:30
|
|
|
constitutive_j2_aTolState ! relevant state values for the current instance of this plasticity
|
2009-09-18 21:07:14 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_aTolState = constitutive_j2_aTolResistance(myInstance)
|
2009-09-18 21:07:14 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function constitutive_j2_aTolState
|
2009-09-18 21:07:14 +05:30
|
|
|
|
|
|
|
|
2012-11-07 21:13:29 +05:30
|
|
|
pure function constitutive_j2_homogenizedC(state,ipc,ip,el)
|
2009-03-06 15:43:08 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* homogenized elacticity matrix *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - state : state variables *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!*********************************************************************
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: p_vec
|
2009-03-06 15:43:08 +05:30
|
|
|
use mesh, only: mesh_NcpElems,mesh_maxNips
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: homogenization_maxNgrains,material_phase, phase_plasticityInstance
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2009-03-06 15:43:08 +05:30
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: ipc,ip,el
|
2012-11-07 21:13:29 +05:30
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: state
|
2012-03-09 01:55:28 +05:30
|
|
|
integer(pInt) :: matID
|
2009-03-06 15:43:08 +05:30
|
|
|
real(pReal), dimension(6,6) :: constitutive_j2_homogenizedC
|
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
matID = phase_plasticityInstance(material_phase(ipc,ip,el))
|
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
|
|
|
constitutive_j2_homogenizedC = constitutive_j2_Cslip_66(1:6,1:6,matID)
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function constitutive_j2_homogenizedC
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
|
|
|
subroutine constitutive_j2_microstructure(Temperature,state,ipc,ip,el)
|
|
|
|
!*********************************************************************
|
|
|
|
!* calculate derived quantities from state (not used here) *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - Tp : temperature *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!*********************************************************************
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: p_vec
|
2009-03-06 15:43:08 +05:30
|
|
|
use mesh, only: mesh_NcpElems,mesh_maxNips
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: homogenization_maxNgrains,material_phase, phase_plasticityInstance
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2009-03-06 15:43:08 +05:30
|
|
|
implicit none
|
|
|
|
!* Definition of variables
|
|
|
|
integer(pInt) ipc,ip,el, matID
|
|
|
|
real(pReal) Temperature
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: state
|
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
matID = phase_plasticityInstance(material_phase(ipc,ip,el))
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine constitutive_j2_microstructure
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
2009-06-23 16:09:29 +05:30
|
|
|
!****************************************************************
|
|
|
|
!* calculates plastic velocity gradient and its tangent *
|
|
|
|
!****************************************************************
|
|
|
|
pure subroutine constitutive_j2_LpAndItsTangent(Lp, dLp_dTstar_99, Tstar_dev_v, Temperature, state, g, ip, el)
|
|
|
|
|
|
|
|
!*** variables and functions from other modules ***!
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: p_vec
|
2009-06-23 16:09:29 +05:30
|
|
|
use math, only: math_mul6x6, &
|
|
|
|
math_Mandel6to33, &
|
2012-01-26 19:20:00 +05:30
|
|
|
math_Plain3333to99
|
2009-06-23 16:09:29 +05:30
|
|
|
use mesh, only: mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
2012-03-12 19:39:37 +05:30
|
|
|
phase_plasticityInstance
|
2009-06-23 16:09:29 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
!*** input variables ***!
|
|
|
|
real(pReal), dimension(6), intent(in):: Tstar_dev_v ! deviatoric part of the 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in):: Temperature
|
|
|
|
integer(pInt), intent(in):: g, & ! grain number
|
|
|
|
ip, & ! integration point number
|
|
|
|
el ! element number
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in):: state ! state of the current microstructure
|
|
|
|
|
|
|
|
!*** output variables ***!
|
|
|
|
real(pReal), dimension(3,3), intent(out) :: Lp ! plastic velocity gradient
|
|
|
|
real(pReal), dimension(9,9), intent(out) :: dLp_dTstar_99 ! derivative of Lp with respect to Tstar (9x9 matrix)
|
|
|
|
|
|
|
|
!*** local variables ***!
|
|
|
|
real(pReal), dimension(3,3) :: Tstar_dev_33 ! deviatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor
|
|
|
|
real(pReal), dimension(3,3,3,3) :: dLp_dTstar_3333 ! derivative of Lp with respect to Tstar as 4th order tensor
|
|
|
|
real(pReal) gamma_dot, & ! strainrate
|
|
|
|
norm_Tstar_dev, & ! euclidean norm of Tstar_dev
|
|
|
|
squarenorm_Tstar_dev ! square of the euclidean norm of Tstar_dev
|
|
|
|
integer(pInt) matID, &
|
|
|
|
k, &
|
|
|
|
l, &
|
|
|
|
m, &
|
|
|
|
n
|
2009-03-06 19:00:22 +05:30
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
matID = phase_plasticityInstance(material_phase(g,ip,el))
|
2009-06-23 16:09:29 +05:30
|
|
|
|
|
|
|
! convert Tstar to matrix and calculate euclidean norm
|
|
|
|
Tstar_dev_33 = math_Mandel6to33(Tstar_dev_v)
|
|
|
|
squarenorm_Tstar_dev = math_mul6x6(Tstar_dev_v,Tstar_dev_v)
|
2011-02-25 14:55:53 +05:30
|
|
|
norm_Tstar_dev = sqrt(squarenorm_Tstar_dev)
|
2009-06-23 16:09:29 +05:30
|
|
|
|
|
|
|
! Initialization of Lp and dLp_dTstar
|
|
|
|
Lp = 0.0_pReal
|
|
|
|
dLp_dTstar_99 = 0.0_pReal
|
|
|
|
|
|
|
|
! for Tstar==0 both Lp and dLp_dTstar are zero (if not n==1)
|
2012-02-21 21:30:00 +05:30
|
|
|
if (norm_Tstar_dev > 0_pInt) then
|
2009-06-23 16:09:29 +05:30
|
|
|
|
|
|
|
! Calculation of gamma_dot
|
2011-02-25 14:55:53 +05:30
|
|
|
gamma_dot = constitutive_j2_gdot0(matID) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
2009-06-23 16:09:29 +05:30
|
|
|
/ &!---------------------------------------------------
|
|
|
|
(constitutive_j2_fTaylor(matID) * state(g,ip,el)%p(1)) ) **constitutive_j2_n(matID)
|
|
|
|
|
|
|
|
! Calculation of Lp
|
|
|
|
Lp = Tstar_dev_33/norm_Tstar_dev * gamma_dot/constitutive_j2_fTaylor(matID)
|
|
|
|
|
|
|
|
!* Calculation of the tangent of Lp
|
2012-02-21 21:30:00 +05:30
|
|
|
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
2009-06-23 16:09:29 +05:30
|
|
|
dLp_dTstar_3333(k,l,m,n) = (constitutive_j2_n(matID)-1.0_pReal) * Tstar_dev_33(k,l)*Tstar_dev_33(m,n) / squarenorm_Tstar_dev
|
2012-02-21 21:30:00 +05:30
|
|
|
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt) &
|
2009-06-23 16:09:29 +05:30
|
|
|
dLp_dTstar_3333(k,l,k,l) = dLp_dTstar_3333(k,l,k,l) + 1.0_pReal
|
|
|
|
dLp_dTstar_99 = math_Plain3333to99(gamma_dot / constitutive_j2_fTaylor(matID) * dLp_dTstar_3333 / norm_Tstar_dev)
|
|
|
|
end if
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine constitutive_j2_LpAndItsTangent
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
2009-06-23 16:09:29 +05:30
|
|
|
!****************************************************************
|
|
|
|
!* calculates the rate of change of microstructure *
|
|
|
|
!****************************************************************
|
|
|
|
pure function constitutive_j2_dotState(Tstar_v, Temperature, state, g, ip, el)
|
|
|
|
|
2012-04-11 19:31:02 +05:30
|
|
|
use prec, only: &
|
|
|
|
p_vec
|
|
|
|
use math, only: &
|
|
|
|
math_mul6x6
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: &
|
|
|
|
homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
|
|
|
phase_plasticityInstance
|
2009-06-23 16:09:29 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
!*** input variables ***!
|
|
|
|
real(pReal), dimension(6), intent(in) :: Tstar_v ! 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in) :: Temperature
|
|
|
|
integer(pInt), intent(in):: g, & ! grain number
|
|
|
|
ip, & ! integration point number
|
|
|
|
el ! element number
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: state ! state of the current microstructure
|
|
|
|
|
|
|
|
!*** output variables ***!
|
|
|
|
real(pReal), dimension(1) :: constitutive_j2_dotState ! evolution of state variable
|
|
|
|
|
|
|
|
!*** local variables ***!
|
|
|
|
real(pReal), dimension(6) :: Tstar_dev_v ! deviatoric part of the 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal) gamma_dot, & ! strainrate
|
|
|
|
hardening, & ! hardening coefficient
|
2012-04-11 19:42:30 +05:30
|
|
|
saturation, & ! saturation resistance
|
2009-06-23 16:09:29 +05:30
|
|
|
norm_Tstar_dev ! euclidean norm of Tstar_dev
|
|
|
|
integer(pInt) matID
|
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
matID = phase_plasticityInstance(material_phase(g,ip,el))
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
! deviatoric part of 2nd Piola-Kirchhoff stress
|
|
|
|
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
2009-06-23 16:09:29 +05:30
|
|
|
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
|
|
|
|
2011-02-25 14:55:53 +05:30
|
|
|
norm_Tstar_dev = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
! gamma_dot
|
2011-02-25 14:55:53 +05:30
|
|
|
gamma_dot = constitutive_j2_gdot0(matID) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
2009-06-23 16:09:29 +05:30
|
|
|
/ &!---------------------------------------------------
|
|
|
|
(constitutive_j2_fTaylor(matID) * state(g,ip,el)%p(1)) ) ** constitutive_j2_n(matID)
|
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
! hardening coefficient
|
2012-04-11 19:31:02 +05:30
|
|
|
if (abs(gamma_dot) > 1e-12_pReal) then
|
2012-04-20 17:48:38 +05:30
|
|
|
if (constitutive_j2_tausat_SinhFitA(matID) == 0.0_pReal) then
|
2012-04-11 19:31:02 +05:30
|
|
|
saturation = constitutive_j2_tausat(matID)
|
|
|
|
else
|
|
|
|
saturation = ( constitutive_j2_tausat(matID) &
|
|
|
|
+ ( log( ( gamma_dot / constitutive_j2_tausat_SinhFitA(matID)&
|
|
|
|
)**(1.0_pReal / constitutive_j2_tausat_SinhFitD(matID))&
|
|
|
|
+ sqrt( ( gamma_dot / constitutive_j2_tausat_SinhFitA(matID) &
|
|
|
|
)**(2.0_pReal / constitutive_j2_tausat_SinhFitD(matID)) &
|
|
|
|
+ 1.0_pReal ) &
|
|
|
|
) & ! asinh(K) = ln(K + sqrt(K^2 +1))
|
|
|
|
)**(1.0_pReal / constitutive_j2_tausat_SinhFitC(matID)) &
|
|
|
|
/ ( constitutive_j2_tausat_SinhFitB(matID) &
|
|
|
|
* (gamma_dot / constitutive_j2_gdot0(matID))**(1.0_pReal / constitutive_j2_n(matID)) &
|
|
|
|
) &
|
|
|
|
)
|
|
|
|
endif
|
|
|
|
hardening = ( constitutive_j2_h0(matID) + constitutive_j2_h0_slopeLnRate(matID) * log(gamma_dot) ) &
|
|
|
|
* abs( 1.0_pReal - state(g,ip,el)%p(1)/saturation )**constitutive_j2_a(matID) &
|
|
|
|
* sign(1.0_pReal, 1.0_pReal - state(g,ip,el)%p(1)/saturation)
|
|
|
|
else
|
|
|
|
hardening = 0.0_pReal
|
|
|
|
endif
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
! dotState
|
2012-11-07 21:13:29 +05:30
|
|
|
constitutive_j2_dotState = hardening * gamma_dot
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function constitutive_j2_dotState
|
2009-07-22 21:37:19 +05:30
|
|
|
|
|
|
|
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
!*********************************************************************
|
|
|
|
!* (instantaneous) incremental change of microstructure *
|
|
|
|
!*********************************************************************
|
|
|
|
function constitutive_j2_deltaState(Tstar_v, Temperature, state, g,ip,el)
|
|
|
|
|
|
|
|
use prec, only: pReal, &
|
|
|
|
pInt, &
|
|
|
|
p_vec
|
|
|
|
use mesh, only: mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
|
|
|
phase_plasticityInstance
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
!*** input variables
|
|
|
|
integer(pInt), intent(in) :: g, & ! current grain number
|
|
|
|
ip, & ! current integration point
|
|
|
|
el ! current element number
|
|
|
|
real(pReal), intent(in) :: Temperature ! temperature
|
|
|
|
real(pReal), dimension(6), intent(in) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state ! current microstructural state
|
|
|
|
|
|
|
|
!*** output variables
|
|
|
|
real(pReal), dimension(constitutive_j2_sizeDotState(phase_plasticityInstance(material_phase(g,ip,el)))) :: &
|
|
|
|
constitutive_j2_deltaState ! change of state variables / microstructure
|
|
|
|
|
|
|
|
!*** local variables
|
|
|
|
|
|
|
|
|
|
|
|
constitutive_j2_deltaState = 0.0_pReal
|
|
|
|
|
|
|
|
endfunction
|
|
|
|
|
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
!****************************************************************
|
|
|
|
!* calculates the rate of change of temperature *
|
|
|
|
!****************************************************************
|
|
|
|
pure function constitutive_j2_dotTemperature(Tstar_v, Temperature, state, g, ip, el)
|
|
|
|
|
|
|
|
!*** variables and functions from other modules ***!
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: p_vec
|
2009-07-22 21:37:19 +05:30
|
|
|
use mesh, only: mesh_NcpElems,mesh_maxNips
|
2012-02-21 21:30:00 +05:30
|
|
|
use material, only: homogenization_maxNgrains
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
implicit none
|
|
|
|
!*** input variables ***!
|
|
|
|
real(pReal), dimension(6), intent(in) :: Tstar_v ! 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in) :: Temperature
|
|
|
|
integer(pInt), intent(in):: g, & ! grain number
|
|
|
|
ip, & ! integration point number
|
|
|
|
el ! element number
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: state ! state of the current microstructure
|
|
|
|
|
|
|
|
!*** output variables ***!
|
|
|
|
real(pReal) constitutive_j2_dotTemperature ! rate of change of temperature
|
|
|
|
|
|
|
|
! calculate dotTemperature
|
|
|
|
constitutive_j2_dotTemperature = 0.0_pReal
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function constitutive_j2_dotTemperature
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
|
|
|
!*********************************************************************
|
|
|
|
!* return array of constitutive results *
|
|
|
|
!*********************************************************************
|
2009-06-23 16:09:29 +05:30
|
|
|
pure function constitutive_j2_postResults(Tstar_v, Temperature, dt, state, g, ip, el)
|
|
|
|
|
|
|
|
!*** variables and functions from other modules ***!
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: p_vec
|
2009-06-23 16:09:29 +05:30
|
|
|
use math, only: math_mul6x6
|
|
|
|
use mesh, only: mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
2012-03-12 19:39:37 +05:30
|
|
|
phase_plasticityInstance, &
|
2009-06-23 16:09:29 +05:30
|
|
|
phase_Noutput
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
!*** input variables ***!
|
|
|
|
real(pReal), dimension(6), intent(in):: Tstar_v ! 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in):: Temperature, &
|
|
|
|
dt ! current time increment
|
|
|
|
integer(pInt), intent(in):: g, & ! grain number
|
|
|
|
ip, & ! integration point number
|
|
|
|
el ! element number
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: state ! state of the current microstructure
|
|
|
|
|
|
|
|
!*** output variables ***!
|
2012-03-12 19:39:37 +05:30
|
|
|
real(pReal), dimension(constitutive_j2_sizePostResults(phase_plasticityInstance(material_phase(g,ip,el)))) :: &
|
2009-06-23 16:09:29 +05:30
|
|
|
constitutive_j2_postResults
|
|
|
|
|
|
|
|
!*** local variables ***!
|
|
|
|
real(pReal), dimension(6) :: Tstar_dev_v ! deviatoric part of the 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal) norm_Tstar_dev ! euclidean norm of Tstar_dev
|
|
|
|
integer(pInt) matID, &
|
|
|
|
o, &
|
|
|
|
c
|
|
|
|
|
|
|
|
!*** global variables ***!
|
|
|
|
! constitutive_j2_gdot0
|
|
|
|
! constitutive_j2_fTaylor
|
|
|
|
! constitutive_j2_n
|
|
|
|
|
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
matID = phase_plasticityInstance(material_phase(g,ip,el))
|
2009-06-23 16:09:29 +05:30
|
|
|
|
|
|
|
! calculate deviatoric part of 2nd Piola-Kirchhoff stress and its norm
|
2009-07-27 14:53:39 +05:30
|
|
|
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
2009-06-23 16:09:29 +05:30
|
|
|
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
2011-02-25 14:55:53 +05:30
|
|
|
norm_Tstar_dev = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
2009-06-23 16:09:29 +05:30
|
|
|
|
|
|
|
c = 0_pInt
|
|
|
|
constitutive_j2_postResults = 0.0_pReal
|
|
|
|
|
2012-02-21 21:30:00 +05:30
|
|
|
do o = 1_pInt,phase_Noutput(material_phase(g,ip,el))
|
2009-06-23 16:09:29 +05:30
|
|
|
select case(constitutive_j2_output(o,matID))
|
|
|
|
case ('flowstress')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_postResults(c+1_pInt) = state(g,ip,el)%p(1)
|
|
|
|
c = c + 1_pInt
|
2009-06-23 16:09:29 +05:30
|
|
|
case ('strainrate')
|
2012-02-21 21:30:00 +05:30
|
|
|
constitutive_j2_postResults(c+1_pInt) = &
|
2011-02-25 14:55:53 +05:30
|
|
|
constitutive_j2_gdot0(matID) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
2009-06-23 16:09:29 +05:30
|
|
|
/ &!---------------------------------------------------
|
|
|
|
(constitutive_j2_fTaylor(matID) * state(g,ip,el)%p(1)) ) ** constitutive_j2_n(matID)
|
2012-02-21 21:30:00 +05:30
|
|
|
c = c + 1_pInt
|
2009-06-23 16:09:29 +05:30
|
|
|
end select
|
|
|
|
enddo
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function constitutive_j2_postResults
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end module constitutive_j2
|