2013-03-22 23:05:05 +05:30
|
|
|
! Copyright 2011-13 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/>.
|
|
|
|
!
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! $Id$
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief Isotropic (J2) Plasticity
|
|
|
|
!> @details Isotropic (J2) Plasticity which resembles the phenopowerlaw plasticity without
|
|
|
|
!! resolving the stress on the slip systems. Will give the response of phenopowerlaw for an
|
|
|
|
!! untextured polycrystal
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
module constitutive_j2
|
2013-06-29 00:28:10 +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
|
2013-06-29 00:28:10 +05:30
|
|
|
character (len=*), parameter, public :: &
|
|
|
|
CONSTITUTIVE_J2_label = 'j2' !< label for this constitutive model
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), dimension(:), allocatable, public :: &
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_sizeDotState, &
|
|
|
|
constitutive_j2_sizeState, &
|
|
|
|
constitutive_j2_sizePostResults
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
|
|
constitutive_j2_sizePostResult !< size of each post result output
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
|
|
constitutive_j2_output !< name of each post result output
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), dimension(:), allocatable, private :: &
|
|
|
|
constitutive_j2_Noutput !< ??
|
2013-01-22 03:27:26 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
character(len=32), dimension(:), allocatable, private :: &
|
2013-01-22 03:27:26 +05:30
|
|
|
constitutive_j2_structureName
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
real(pReal), dimension(:), allocatable, private :: &
|
|
|
|
constitutive_j2_fTaylor, & !< Taylor factor
|
|
|
|
constitutive_j2_tau0, & !< initial plastic stress
|
|
|
|
constitutive_j2_gdot0, & !< reference velocity
|
|
|
|
constitutive_j2_n, & !< Visco-plastic parameter
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! 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, &
|
2013-06-29 00:28:10 +05:30
|
|
|
constitutive_j2_tausat, & !< final plastic stress
|
2012-03-09 01:55:28 +05:30
|
|
|
constitutive_j2_a, &
|
2012-04-11 19:31:02 +05:30
|
|
|
constitutive_j2_aTolResistance, &
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! tausat += (asinh((gammadot / SinhFitA)**(1 / SinhFitD)))**(1 / SinhFitC) / (SinhFitB * (gammadot / gammadot0)**(1/n))
|
|
|
|
constitutive_j2_tausat_SinhFitA, & !< fitting parameter for normalized strain rate vs. stress function
|
|
|
|
constitutive_j2_tausat_SinhFitB, & !< fitting parameter for normalized strain rate vs. stress function
|
|
|
|
constitutive_j2_tausat_SinhFitC, & !< fitting parameter for normalized strain rate vs. stress function
|
|
|
|
constitutive_j2_tausat_SinhFitD !< fitting parameter for normalized strain rate vs. stress function
|
|
|
|
|
|
|
|
|
|
|
|
real(pReal), dimension(:,:,:), allocatable, private :: &
|
2012-04-11 19:31:02 +05:30
|
|
|
constitutive_j2_Cslip_66
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
public :: &
|
|
|
|
constitutive_j2_init, &
|
|
|
|
constitutive_j2_stateInit, &
|
|
|
|
constitutive_j2_aTolState, &
|
|
|
|
constitutive_j2_homogenizedC, &
|
|
|
|
constitutive_j2_microstructure, &
|
|
|
|
constitutive_j2_LpAndItsTangent, &
|
|
|
|
constitutive_j2_dotState, &
|
|
|
|
constitutive_j2_deltaState, &
|
|
|
|
constitutive_j2_dotTemperature, &
|
|
|
|
constitutive_j2_postResults
|
2012-03-09 01:55:28 +05:30
|
|
|
|
|
|
|
contains
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief module initialization
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
subroutine constitutive_j2_init(myFile)
|
2013-06-29 00:28:10 +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, &
|
2013-02-25 22:04:59 +05:30
|
|
|
IO_error, &
|
2013-06-29 00:28:10 +05:30
|
|
|
IO_timeStamp, &
|
|
|
|
IO_read
|
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
|
2013-06-29 00:28:10 +05:30
|
|
|
use lattice, only: &
|
|
|
|
lattice_symmetrizeC66
|
2012-03-09 01:55:28 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: myFile
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), parameter :: MAXNCHUNKS = 7_pInt
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), dimension(1_pInt+2_pInt*MAXNCHUNKS) :: positions
|
2013-02-11 16:13:45 +05:30
|
|
|
integer(pInt) :: section = 0_pInt, maxNinstance, i,o, mySize
|
2013-06-29 00:28:10 +05:30
|
|
|
character(len=65536) :: &
|
|
|
|
tag = '', &
|
|
|
|
line = '' ! to start initialized
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- constitutive_'//trim(CONSTITUTIVE_J2_label)//' init -+>>>'
|
2013-05-28 23:01:55 +05:30
|
|
|
write(6,'(a)') ' $Id$'
|
|
|
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
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-06-29 00:28:10 +05:30
|
|
|
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
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
|
2013-01-22 03:27:26 +05:30
|
|
|
allocate(constitutive_j2_structureName(maxNinstance))
|
|
|
|
constitutive_j2_structureName = ''
|
2012-03-09 01:55:28 +05:30
|
|
|
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
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
do while (trim(line) /= '#EOF#' .and. IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
2013-06-27 00:49:00 +05:30
|
|
|
line = IO_read(myFile)
|
2009-03-06 15:43:08 +05:30
|
|
|
enddo
|
2012-02-14 05:00:59 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
do while (trim(line) /= '#EOF#') ! read through sections of phase part
|
2013-06-27 00:49:00 +05:30
|
|
|
line = IO_read(myFile)
|
2013-06-29 00:28:10 +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
|
2012-02-14 05:00:59 +05:30
|
|
|
cycle
|
2009-03-06 15:43:08 +05:30
|
|
|
endif
|
2013-06-29 00:28:10 +05:30
|
|
|
if (section > 0_pInt ) then ! do not short-circuit here (.and. with next if-statement). It's not safe in Fortran
|
|
|
|
if (phase_plasticity(section) == CONSTITUTIVE_J2_label) then ! one of my sections
|
|
|
|
i = phase_plasticityInstance(section) ! which instance of my plasticity is present phase
|
2013-06-12 01:46:40 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
2013-06-29 00:28:10 +05:30
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
|
2013-06-12 01:46:40 +05:30
|
|
|
select case(tag)
|
|
|
|
case ('plasticity','elasticity')
|
|
|
|
cycle
|
|
|
|
case ('(output)')
|
|
|
|
constitutive_j2_Noutput(i) = constitutive_j2_Noutput(i) + 1_pInt
|
2013-06-29 00:28:10 +05:30
|
|
|
constitutive_j2_output(constitutive_j2_Noutput(i),i) = &
|
|
|
|
IO_lc(IO_stringValue(line,positions,2_pInt))
|
2013-06-12 01:46:40 +05:30
|
|
|
case ('lattice_structure')
|
|
|
|
constitutive_j2_structureName(i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
|
|
|
case ('c11')
|
|
|
|
constitutive_j2_Cslip_66(1,1,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c12')
|
|
|
|
constitutive_j2_Cslip_66(1,2,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c13')
|
|
|
|
constitutive_j2_Cslip_66(1,3,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c22')
|
|
|
|
constitutive_j2_Cslip_66(2,2,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c23')
|
|
|
|
constitutive_j2_Cslip_66(2,3,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c33')
|
|
|
|
constitutive_j2_Cslip_66(3,3,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c44')
|
|
|
|
constitutive_j2_Cslip_66(4,4,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c55')
|
|
|
|
constitutive_j2_Cslip_66(5,5,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('c66')
|
|
|
|
constitutive_j2_Cslip_66(6,6,i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('tau0')
|
|
|
|
constitutive_j2_tau0(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('gdot0')
|
|
|
|
constitutive_j2_gdot0(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('n')
|
|
|
|
constitutive_j2_n(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('h0')
|
|
|
|
constitutive_j2_h0(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('h0_slope','slopelnrate')
|
|
|
|
constitutive_j2_h0_slopeLnRate(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('tausat')
|
|
|
|
constitutive_j2_tausat(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('tausat_sinhfita')
|
|
|
|
constitutive_j2_tausat_SinhFitA(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('tausat_sinhfitb')
|
|
|
|
constitutive_j2_tausat_SinhFitB(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('tausat_sinhfitc')
|
|
|
|
constitutive_j2_tausat_SinhFitC(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('tausat_sinhfitd')
|
|
|
|
constitutive_j2_tausat_SinhFitD(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('a', 'w0')
|
|
|
|
constitutive_j2_a(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('taylorfactor')
|
|
|
|
constitutive_j2_fTaylor(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case ('atol_resistance')
|
|
|
|
constitutive_j2_aTolResistance(i) = IO_floatValue(line,positions,2_pInt)
|
|
|
|
case default
|
2013-06-27 22:11:00 +05:30
|
|
|
call IO_error(210_pInt,ext_msg=trim(tag)//' ('//constitutive_j2_label//')')
|
2013-06-12 01:46:40 +05:30
|
|
|
end select
|
|
|
|
endif
|
2009-03-06 15:43:08 +05:30
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
sanityChecks: do i = 1_pInt,maxNinstance
|
|
|
|
if (constitutive_j2_structureName(i) == '') call IO_error(205_pInt,e=i)
|
|
|
|
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//')')
|
|
|
|
enddo sanityChecks
|
2009-03-06 15:43:08 +05:30
|
|
|
|
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
|
2013-06-29 00:28:10 +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
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
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
|
2013-01-22 03:27:26 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
constitutive_j2_Cslip_66(1:6,1:6,i) = lattice_symmetrizeC66(constitutive_j2_structureName(i),&
|
|
|
|
constitutive_j2_Cslip_66(1:6,1:6,i))
|
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) = &
|
2013-06-29 00:28:10 +05:30
|
|
|
math_Mandel3333to66(math_Voigt66to3333(constitutive_j2_Cslip_66(1:6,1:6,i))) ! todo what is going on here?
|
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
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief initial microstructural state
|
|
|
|
!> @detail initial microstructural state is set to the value specified by tau0
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2009-06-23 16:09:29 +05:30
|
|
|
pure function constitutive_j2_stateInit(myInstance)
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
2013-06-29 00:28:10 +05:30
|
|
|
real(pReal), dimension(1) :: constitutive_j2_stateInit
|
|
|
|
integer(pInt), intent(in) :: myInstance !< number specifying the instance of the plasticity
|
|
|
|
|
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
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief relevant state values for the current instance of this plasticity
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
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
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), intent(in) :: myInstance !< number specifying the instance of the plasticity
|
2009-09-18 21:07:14 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
real(pReal), dimension(constitutive_j2_sizeState(myInstance)) :: &
|
2013-06-29 00:28:10 +05:30
|
|
|
constitutive_j2_aTolState
|
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
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief homogenized elasticity matrix
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-11-07 21:13:29 +05:30
|
|
|
pure function constitutive_j2_homogenizedC(state,ipc,ip,el)
|
2013-06-29 00:28:10 +05:30
|
|
|
use prec, only: &
|
|
|
|
p_vec
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_NcpElems,mesh_maxNips
|
|
|
|
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
|
|
|
|
real(pReal), dimension(6,6) :: constitutive_j2_homogenizedC
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ipc, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state !< microstructure state
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
constitutive_j2_homogenizedC = constitutive_j2_Cslip_66(1:6,1:6,&
|
|
|
|
phase_plasticityInstance(material_phase(ipc,ip,el)))
|
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
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief calculate derived quantities from state (not used here)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure subroutine constitutive_j2_microstructure(temperature,state,ipc,ip,el)
|
|
|
|
use prec, only: &
|
|
|
|
p_vec
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_NcpElems,&
|
|
|
|
mesh_maxNips
|
|
|
|
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
|
2013-06-29 00:28:10 +05:30
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ipc, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
temperature !< temperature at IP
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state !< microstructure state
|
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
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief calculates plastic velocity gradient and its tangent
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure subroutine constitutive_j2_LpAndItsTangent(Lp,dLp_dTstar_99,Tstar_v,&
|
|
|
|
temperature,state,ipc,ip,el)
|
|
|
|
use prec, only: &
|
|
|
|
p_vec
|
|
|
|
use math, only: &
|
|
|
|
math_mul6x6, &
|
|
|
|
math_Mandel6to33, &
|
|
|
|
math_Plain3333to99, &
|
|
|
|
math_deviatoric33, &
|
|
|
|
math_mul33xx33
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: &
|
|
|
|
homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
|
|
|
phase_plasticityInstance
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
implicit none
|
|
|
|
real(pReal), dimension(6), intent(in) :: &
|
|
|
|
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
temperature !< temperature at IP
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ipc, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state !< microstructure state
|
|
|
|
|
|
|
|
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 2nd Piola Kirchhoff stress
|
|
|
|
|
|
|
|
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-06-23 16:09:29 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
matID = phase_plasticityInstance(material_phase(ipc,ip,el))
|
|
|
|
Tstar_dev_33 = math_deviatoric33(math_Mandel6to33(Tstar_v)) ! deviatoric part of 2nd Piola-Kirchhoff stress
|
|
|
|
squarenorm_Tstar_dev = math_mul33xx33(Tstar_dev_33,Tstar_dev_33)
|
|
|
|
norm_Tstar_dev = sqrt(squarenorm_Tstar_dev)
|
|
|
|
|
|
|
|
if (norm_Tstar_dev <= 0.0_pReal) then ! Tstar == 0 --> both Lp and dLp_dTstar are zero
|
|
|
|
Lp = 0.0_pReal
|
|
|
|
dLp_dTstar_99 = 0.0_pReal
|
|
|
|
else
|
|
|
|
gamma_dot = constitutive_j2_gdot0(matID) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
|
|
|
/ &!----------------------------------------------------------------------------------
|
|
|
|
(constitutive_j2_fTaylor(matID) * state(ipc,ip,el)%p(1)) ) **constitutive_j2_n(matID)
|
|
|
|
|
|
|
|
Lp = Tstar_dev_33/norm_Tstar_dev * gamma_dot/constitutive_j2_fTaylor(matID)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! Calculation of the tangent of Lp
|
|
|
|
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
|
|
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
|
|
|
|
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt) &
|
|
|
|
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
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine constitutive_j2_LpAndItsTangent
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief calculates the rate of change of microstructure
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function constitutive_j2_dotState(Tstar_v,Temperature,state,ipc,ip, el)
|
|
|
|
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
|
2012-05-16 20:13:26 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
implicit none
|
|
|
|
real(pReal), dimension(1) :: &
|
|
|
|
constitutive_j2_dotState
|
|
|
|
real(pReal), dimension(6), intent(in):: &
|
|
|
|
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
Temperature !< temperature at integration point
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ipc, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state !< microstructure state
|
|
|
|
|
|
|
|
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
|
|
|
|
saturation, & !< saturation resistance
|
|
|
|
norm_Tstar_dev !< euclidean norm of Tstar_dev
|
|
|
|
integer(pInt) :: &
|
|
|
|
matID
|
2012-05-16 20:13:26 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
matID = phase_plasticityInstance(material_phase(ipc,ip,el))
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! norm of deviatoric part of 2nd Piola-Kirchhoff stress
|
|
|
|
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
|
|
|
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
|
|
|
norm_Tstar_dev = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! strain rate
|
|
|
|
gamma_dot = constitutive_j2_gdot0(matID) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
|
|
|
/ &!-----------------------------------------------------------------------------------
|
|
|
|
(constitutive_j2_fTaylor(matID) * state(ipc,ip,el)%p(1)) ) ** constitutive_j2_n(matID)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! hardening coefficient
|
|
|
|
if (abs(gamma_dot) > 1e-12_pReal) then
|
|
|
|
if (constitutive_j2_tausat_SinhFitA(matID) == 0.0_pReal) then
|
|
|
|
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(ipc,ip,el)%p(1)/saturation )**constitutive_j2_a(matID) &
|
|
|
|
* sign(1.0_pReal, 1.0_pReal - state(ipc,ip,el)%p(1)/saturation)
|
|
|
|
else
|
|
|
|
hardening = 0.0_pReal
|
|
|
|
endif
|
|
|
|
|
|
|
|
constitutive_j2_dotState = hardening * gamma_dot
|
2012-05-16 20:13:26 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
end function constitutive_j2_dotState
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief (instantaneous) incremental change of microstructure (dummy function)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function constitutive_j2_deltaState(Tstar_v,temperature,state,ipc,ip,el)
|
|
|
|
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
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
real(pReal), dimension(6), intent(in):: &
|
|
|
|
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
Temperature !< temperature at integration point
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ipc, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state !< microstructure state
|
|
|
|
|
|
|
|
real(pReal), dimension(constitutive_j2_sizeDotState(phase_plasticityInstance(material_phase(ipc,ip,el)))) :: &
|
|
|
|
constitutive_j2_deltaState
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
constitutive_j2_deltaState = 0.0_pReal
|
|
|
|
|
|
|
|
end function constitutive_j2_deltaState
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief calculates the rate of change of temperature (dummy function)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
real(pReal) pure function constitutive_j2_dotTemperature(Tstar_v,temperature,state,ipc,ip,el)
|
|
|
|
use prec, only: &
|
|
|
|
p_vec
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: &
|
|
|
|
homogenization_maxNgrains
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
real(pReal), dimension(6), intent(in) :: &
|
|
|
|
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
temperature !< temperature at integration point
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ipc, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state !< microstructure state
|
|
|
|
|
|
|
|
constitutive_j2_dotTemperature = 0.0_pReal
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function constitutive_j2_dotTemperature
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
2013-06-29 00:28:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief return array of constitutive results
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function constitutive_j2_postResults(Tstar_v,temperature,dt,state,ipc,ip,el)
|
|
|
|
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, &
|
|
|
|
phase_Noutput
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
real(pReal), dimension(6), intent(in) :: &
|
|
|
|
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
temperature, & !< temperature at integration point
|
|
|
|
dt
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ipc, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
state
|
|
|
|
real(pReal), dimension(constitutive_j2_sizePostResults(phase_plasticityInstance(material_phase(ipc,ip,el)))) :: &
|
|
|
|
constitutive_j2_postResults
|
|
|
|
|
|
|
|
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
|
|
|
|
|
|
|
|
matID = phase_plasticityInstance(material_phase(ipc,ip,el))
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! calculate deviatoric part of 2nd Piola-Kirchhoff stress and its norm
|
|
|
|
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
|
|
|
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
|
|
|
norm_Tstar_dev = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
|
|
|
|
|
|
|
c = 0_pInt
|
|
|
|
constitutive_j2_postResults = 0.0_pReal
|
|
|
|
|
|
|
|
outputsLoop: do o = 1_pInt,phase_Noutput(material_phase(ipc,ip,el))
|
|
|
|
select case(constitutive_j2_output(o,matID))
|
|
|
|
case ('flowstress')
|
|
|
|
constitutive_j2_postResults(c+1_pInt) = state(ipc,ip,el)%p(1)
|
|
|
|
c = c + 1_pInt
|
|
|
|
case ('strainrate')
|
|
|
|
constitutive_j2_postResults(c+1_pInt) = &
|
|
|
|
constitutive_j2_gdot0(matID) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
|
|
|
/ &!----------------------------------------------------------------------------------
|
|
|
|
(constitutive_j2_fTaylor(matID) * state(ipc,ip,el)%p(1)) ) ** constitutive_j2_n(matID)
|
|
|
|
c = c + 1_pInt
|
|
|
|
end select
|
|
|
|
enddo outputsLoop
|
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
|