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]
|
|
|
|
! constitution j2
|
|
|
|
! (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
|
|
|
|
|
|
|
MODULE constitutive_j2
|
|
|
|
|
|
|
|
!*** Include other modules ***
|
|
|
|
use prec, only: pReal,pInt
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
character (len=*), parameter :: constitutive_j2_label = 'j2'
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: constitutive_j2_sizeDotState, &
|
|
|
|
constitutive_j2_sizeState, &
|
|
|
|
constitutive_j2_sizePostResults
|
2009-07-22 21:37:19 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable,target :: constitutive_j2_sizePostResult ! size of each post result output
|
|
|
|
character(len=64), dimension(:,:), allocatable,target :: constitutive_j2_output ! name of each post result output
|
2009-03-06 15:43:08 +05:30
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_C11
|
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_C12
|
|
|
|
real(pReal), dimension(:,:,:), allocatable :: constitutive_j2_Cslip_66
|
|
|
|
!* Visco-plastic constitutive_j2 parameters
|
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_fTaylor
|
2009-06-23 16:09:29 +05:30
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_tau0
|
2009-03-06 15:43:08 +05:30
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_gdot0
|
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_n
|
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_h0
|
2009-07-22 21:37:19 +05:30
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_tausat
|
2011-11-23 20:18:39 +05:30
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_a
|
2010-10-26 18:46:37 +05:30
|
|
|
real(pReal), dimension(:), allocatable :: constitutive_j2_aTolResistance
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
|
|
|
|
CONTAINS
|
|
|
|
!****************************************
|
2009-03-06 22:23:31 +05:30
|
|
|
!* - constitutive_j2_init
|
|
|
|
!* - constitutive_j2_stateInit
|
|
|
|
!* - constitutive_j2_homogenizedC
|
|
|
|
!* - constitutive_j2_microstructure
|
|
|
|
!* - constitutive_j2_LpAndItsTangent
|
|
|
|
!* - consistutive_j2_dotState
|
|
|
|
!* - consistutive_j2_postResults
|
2009-03-06 15:43:08 +05:30
|
|
|
!****************************************
|
|
|
|
|
|
|
|
|
|
|
|
subroutine constitutive_j2_init(file)
|
|
|
|
!**************************************
|
|
|
|
!* Module initialization *
|
|
|
|
!**************************************
|
|
|
|
use prec, only: pInt, pReal
|
|
|
|
use math, only: math_Mandel3333to66, math_Voigt66to3333
|
|
|
|
use IO
|
|
|
|
use material
|
2011-03-21 16:01:17 +05:30
|
|
|
use debug, only: debug_verbosity
|
2009-03-06 15:43:08 +05:30
|
|
|
integer(pInt), intent(in) :: file
|
|
|
|
integer(pInt), parameter :: maxNchunks = 7
|
|
|
|
integer(pInt), dimension(1+2*maxNchunks) :: positions
|
2011-04-13 19:46:22 +05:30
|
|
|
integer(pInt) section, maxNinstance, i,j,k, output, mySize
|
2009-03-06 15:43:08 +05:30
|
|
|
character(len=64) tag
|
|
|
|
character(len=1024) line
|
2009-07-22 21:37:19 +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
|
|
|
!$OMP CRITICAL (write2out)
|
2011-03-21 16:01:17 +05:30
|
|
|
write(6,*)
|
2011-08-26 19:27:29 +05:30
|
|
|
write(6,*) '<<<+- constitutive_',trim(constitutive_j2_label),' init -+>>>'
|
2011-03-21 16:01:17 +05:30
|
|
|
write(6,*) '$Id$'
|
2012-02-01 00:48:55 +05:30
|
|
|
#include "compilation_info.f90"
|
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
|
|
|
!$OMP END CRITICAL (write2out)
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
maxNinstance = count(phase_constitution == constitutive_j2_label)
|
|
|
|
if (maxNinstance == 0) return
|
|
|
|
|
2011-03-21 16:01:17 +05:30
|
|
|
if (debug_verbosity > 0) then
|
|
|
|
!$OMP CRITICAL (write2out)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a16,1x,i5)') '# instances:',maxNinstance
|
2011-03-21 16:01:17 +05:30
|
|
|
write(6,*)
|
|
|
|
!$OMP END CRITICAL (write2out)
|
|
|
|
endif
|
2009-10-16 01:32:52 +05:30
|
|
|
|
2009-09-18 21:07:14 +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_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
|
|
|
|
allocate(constitutive_j2_tausat(maxNinstance)) ; constitutive_j2_tausat = 0.0_pReal
|
2011-11-23 20:18:39 +05:30
|
|
|
allocate(constitutive_j2_a(maxNinstance)) ; constitutive_j2_a = 0.0_pReal
|
2010-10-26 18:46:37 +05:30
|
|
|
allocate(constitutive_j2_aTolResistance(maxNinstance)) ; constitutive_j2_aTolResistance = 0.0_pReal
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
rewind(file)
|
|
|
|
line = ''
|
|
|
|
section = 0
|
|
|
|
|
|
|
|
do while (IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
|
|
|
read(file,'(a1024)',END=100) line
|
|
|
|
enddo
|
|
|
|
|
|
|
|
do ! read thru sections of phase part
|
|
|
|
read(file,'(a1024)',END=100) line
|
|
|
|
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
|
|
|
|
output = 0 ! reset output counter
|
|
|
|
endif
|
|
|
|
if (section > 0 .and. phase_constitution(section) == constitutive_j2_label) then ! one of my sections
|
2009-03-26 14:13:31 +05:30
|
|
|
i = phase_constitutionInstance(section) ! which instance of my constitution is present phase
|
2009-03-06 15:43:08 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
|
|
|
|
select case(tag)
|
|
|
|
case ('(output)')
|
|
|
|
output = output + 1
|
|
|
|
constitutive_j2_output(output,i) = IO_lc(IO_stringValue(line,positions,2))
|
|
|
|
case ('c11')
|
|
|
|
constitutive_j2_C11(i) = IO_floatValue(line,positions,2)
|
|
|
|
case ('c12')
|
|
|
|
constitutive_j2_C12(i) = IO_floatValue(line,positions,2)
|
2009-06-23 16:09:29 +05:30
|
|
|
case ('tau0')
|
|
|
|
constitutive_j2_tau0(i) = IO_floatValue(line,positions,2)
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('gdot0')
|
|
|
|
constitutive_j2_gdot0(i) = IO_floatValue(line,positions,2)
|
|
|
|
case ('n')
|
|
|
|
constitutive_j2_n(i) = IO_floatValue(line,positions,2)
|
|
|
|
case ('h0')
|
|
|
|
constitutive_j2_h0(i) = IO_floatValue(line,positions,2)
|
2009-07-22 21:37:19 +05:30
|
|
|
case ('tausat')
|
|
|
|
constitutive_j2_tausat(i) = IO_floatValue(line,positions,2)
|
2011-11-23 20:18:39 +05:30
|
|
|
case ('a', 'w0')
|
|
|
|
constitutive_j2_a(i) = IO_floatValue(line,positions,2)
|
2009-03-06 15:43:08 +05:30
|
|
|
case ('taylorfactor')
|
|
|
|
constitutive_j2_fTaylor(i) = IO_floatValue(line,positions,2)
|
2010-10-26 18:46:37 +05:30
|
|
|
case ('atol_resistance')
|
|
|
|
constitutive_j2_aTolResistance(i) = IO_floatValue(line,positions,2)
|
2009-03-06 15:43:08 +05:30
|
|
|
end select
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
|
|
|
100 do i = 1,maxNinstance ! sanity checks
|
2009-09-18 21:07:14 +05:30
|
|
|
if (constitutive_j2_tau0(i) < 0.0_pReal) call IO_error(210)
|
|
|
|
if (constitutive_j2_gdot0(i) <= 0.0_pReal) call IO_error(211)
|
|
|
|
if (constitutive_j2_n(i) <= 0.0_pReal) call IO_error(212)
|
|
|
|
if (constitutive_j2_tausat(i) <= 0.0_pReal) call IO_error(213)
|
2011-11-23 20:18:39 +05:30
|
|
|
if (constitutive_j2_a(i) <= 0.0_pReal) call IO_error(241)
|
2009-09-18 21:07:14 +05:30
|
|
|
if (constitutive_j2_fTaylor(i) <= 0.0_pReal) call IO_error(240)
|
2010-10-26 18:46:37 +05:30
|
|
|
if (constitutive_j2_aTolResistance(i) <= 0.0_pReal) call IO_error(242)
|
2009-03-06 15:43:08 +05:30
|
|
|
enddo
|
|
|
|
|
|
|
|
do i = 1,maxNinstance
|
|
|
|
do j = 1,maxval(phase_Noutput)
|
2010-10-26 18:46:37 +05:30
|
|
|
select case(constitutive_j2_output(j,i))
|
|
|
|
case('flowstress')
|
|
|
|
mySize = 1_pInt
|
|
|
|
case('strainrate')
|
|
|
|
mySize = 1_pInt
|
|
|
|
case default
|
|
|
|
mySize = 0_pInt
|
|
|
|
end select
|
|
|
|
|
|
|
|
if (mySize > 0_pInt) then ! any meaningful output found
|
|
|
|
constitutive_j2_sizePostResult(j,i) = mySize
|
|
|
|
constitutive_j2_sizePostResults(i) = &
|
|
|
|
constitutive_j2_sizePostResults(i) + mySize
|
|
|
|
endif
|
2009-03-06 15:43:08 +05:30
|
|
|
enddo
|
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
constitutive_j2_sizeDotState(i) = 1
|
|
|
|
constitutive_j2_sizeState(i) = 1
|
|
|
|
|
2009-03-06 15:43:08 +05:30
|
|
|
forall(k=1:3)
|
|
|
|
forall(j=1:3) &
|
2009-07-22 21:37:19 +05:30
|
|
|
constitutive_j2_Cslip_66(k,j,i) = constitutive_j2_C12(i)
|
|
|
|
constitutive_j2_Cslip_66(k,k,i) = constitutive_j2_C11(i)
|
|
|
|
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
|
|
|
|
|
|
|
|
return
|
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endsubroutine
|
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)
|
|
|
|
|
|
|
|
use prec, only: pReal,pInt
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
integer(pInt), intent(in) :: myInstance
|
|
|
|
real(pReal), dimension(1) :: constitutive_j2_stateInit
|
|
|
|
|
|
|
|
constitutive_j2_stateInit = constitutive_j2_tau0(myInstance)
|
|
|
|
|
|
|
|
return
|
2009-06-15 18:41:21 +05:30
|
|
|
endfunction
|
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
|
|
|
|
|
|
|
use prec, only: pReal, &
|
|
|
|
pInt
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
!*** input variables
|
|
|
|
integer(pInt), intent(in) :: myInstance ! number specifying the current instance of the constitution
|
|
|
|
|
|
|
|
!*** output variables
|
|
|
|
real(pReal), dimension(constitutive_j2_sizeState(myInstance)) :: &
|
2010-10-26 18:46:37 +05:30
|
|
|
constitutive_j2_aTolState ! relevant state values for the current instance of this constitution
|
2009-09-18 21:07:14 +05:30
|
|
|
|
|
|
|
!*** local variables
|
|
|
|
|
2010-10-26 18:46:37 +05:30
|
|
|
constitutive_j2_aTolState = constitutive_j2_aTolResistance(myInstance)
|
2009-09-18 21:07:14 +05:30
|
|
|
|
|
|
|
endfunction
|
|
|
|
|
|
|
|
|
2009-03-06 15:43:08 +05:30
|
|
|
function constitutive_j2_homogenizedC(state,ipc,ip,el)
|
|
|
|
!*********************************************************************
|
|
|
|
!* homogenized elacticity matrix *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - state : state variables *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!*********************************************************************
|
|
|
|
use prec, only: pReal,pInt,p_vec
|
|
|
|
use mesh, only: mesh_NcpElems,mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains,material_phase, phase_constitutionInstance
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
integer(pInt), intent(in) :: ipc,ip,el
|
|
|
|
integer(pInt) matID
|
|
|
|
real(pReal), dimension(6,6) :: constitutive_j2_homogenizedC
|
|
|
|
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: state
|
|
|
|
|
|
|
|
matID = phase_constitutionInstance(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
|
|
|
|
|
|
|
return
|
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endfunction
|
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 *
|
|
|
|
!*********************************************************************
|
|
|
|
use prec, only: pReal,pInt,p_vec
|
|
|
|
use mesh, only: mesh_NcpElems,mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains,material_phase, phase_constitutionInstance
|
|
|
|
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
|
|
|
|
|
|
|
|
matID = phase_constitutionInstance(material_phase(ipc,ip,el))
|
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endsubroutine
|
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 ***!
|
|
|
|
use prec, only: pReal, &
|
|
|
|
pInt, &
|
|
|
|
p_vec
|
|
|
|
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 lattice, only: lattice_Sslip, &
|
|
|
|
lattice_Sslip_v
|
|
|
|
use mesh, only: mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
|
|
|
phase_constitutionInstance
|
|
|
|
|
|
|
|
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
|
|
|
|
2009-06-23 16:09:29 +05:30
|
|
|
matID = phase_constitutionInstance(material_phase(g,ip,el))
|
|
|
|
|
|
|
|
! 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)
|
|
|
|
if (norm_Tstar_dev > 0) then
|
|
|
|
|
|
|
|
! 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
|
|
|
|
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
|
|
|
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:3,l=1:3) &
|
|
|
|
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
|
|
|
|
|
|
|
|
return
|
2009-03-06 16:58:48 +05:30
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endsubroutine
|
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)
|
|
|
|
|
|
|
|
!*** variables and functions from other modules ***!
|
|
|
|
use prec, only: pReal, &
|
|
|
|
pInt, &
|
|
|
|
p_vec
|
|
|
|
use math, only: math_mul6x6
|
|
|
|
use lattice, only: lattice_Sslip_v
|
|
|
|
use mesh, only: mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
|
|
|
phase_constitutionInstance
|
|
|
|
|
|
|
|
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
|
|
|
|
norm_Tstar_dev ! euclidean norm of Tstar_dev
|
|
|
|
integer(pInt) matID
|
|
|
|
|
|
|
|
matID = phase_constitutionInstance(material_phase(g,ip,el))
|
|
|
|
|
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
|
2009-06-23 16:09:29 +05:30
|
|
|
hardening = constitutive_j2_h0(matID) * &
|
2011-11-23 20:18:39 +05:30
|
|
|
( 1.0_pReal - state(g,ip,el)%p(1) / constitutive_j2_tausat(matID) ) ** constitutive_j2_a(matID)
|
2009-06-23 16:09:29 +05:30
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
! dotState
|
2009-06-23 16:09:29 +05:30
|
|
|
constitutive_j2_dotState = hardening * gamma_dot
|
|
|
|
|
|
|
|
return
|
2009-03-06 15:43:08 +05:30
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
endfunction
|
|
|
|
|
|
|
|
|
|
|
|
!****************************************************************
|
|
|
|
!* 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 ***!
|
|
|
|
use prec, only: pReal,pInt,p_vec
|
|
|
|
use lattice, only: lattice_Sslip_v
|
|
|
|
use mesh, only: mesh_NcpElems,mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains,material_phase,phase_constitutionInstance
|
|
|
|
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
|
|
|
|
|
|
|
|
return
|
2009-06-15 18:41:21 +05:30
|
|
|
endfunction
|
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 ***!
|
|
|
|
use prec, only: pReal, &
|
|
|
|
pInt, &
|
|
|
|
p_vec
|
|
|
|
use math, only: math_mul6x6
|
|
|
|
use lattice, only: lattice_Sslip_v
|
|
|
|
use mesh, only: mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: homogenization_maxNgrains, &
|
|
|
|
material_phase, &
|
|
|
|
phase_constitutionInstance, &
|
|
|
|
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 ***!
|
|
|
|
real(pReal), dimension(constitutive_j2_sizePostResults(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
|
|
|
|
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
|
|
|
|
|
|
|
|
|
|
|
|
matID = phase_constitutionInstance(material_phase(g,ip,el))
|
|
|
|
|
|
|
|
! 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
|
|
|
|
|
|
|
|
do o = 1,phase_Noutput(material_phase(g,ip,el))
|
|
|
|
select case(constitutive_j2_output(o,matID))
|
|
|
|
case ('flowstress')
|
|
|
|
constitutive_j2_postResults(c+1) = state(g,ip,el)%p(1)
|
|
|
|
c = c + 1
|
|
|
|
case ('strainrate')
|
|
|
|
constitutive_j2_postResults(c+1) = &
|
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)
|
|
|
|
c = c + 1
|
|
|
|
end select
|
|
|
|
enddo
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
return
|
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endfunction
|
2009-03-06 15:43:08 +05:30
|
|
|
|
|
|
|
END MODULE
|