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/>.
|
|
|
|
!
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! $Id$
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
module homogenization_isostrain
|
2013-01-28 22:06:26 +05:30
|
|
|
use prec, only: &
|
|
|
|
pInt
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-01-28 22:06:26 +05:30
|
|
|
private
|
|
|
|
character (len=*), parameter, public :: &
|
2012-03-09 01:55:28 +05:30
|
|
|
homogenization_isostrain_label = 'isostrain'
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
integer(pInt), dimension(:), allocatable, public :: &
|
2012-03-09 01:55:28 +05:30
|
|
|
homogenization_isostrain_sizeState, &
|
|
|
|
homogenization_isostrain_sizePostResults
|
2013-01-28 22:06:26 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
2012-03-09 01:55:28 +05:30
|
|
|
homogenization_isostrain_sizePostResult
|
2013-01-28 22:06:26 +05:30
|
|
|
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
|
|
homogenization_isostrain_output !< name of each post result output
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
integer(pInt), dimension(:), allocatable, private :: &
|
|
|
|
homogenization_isostrain_Ngrains
|
|
|
|
|
|
|
|
public :: &
|
|
|
|
homogenization_isostrain_init, &
|
|
|
|
homogenization_isostrain_stateInit, &
|
|
|
|
homogenization_isostrain_partitionDeformation, &
|
|
|
|
homogenization_isostrain_updateState, &
|
|
|
|
homogenization_isostrain_averageStressAndItsTangent, &
|
|
|
|
homogenization_isostrain_averageTemperature, &
|
|
|
|
homogenization_isostrain_postResults
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
contains
|
2013-01-28 22:06:26 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief allocates all neccessary fields, reads information from material configuration file
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine homogenization_isostrain_init(myFile)
|
|
|
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2010-02-25 23:09:11 +05:30
|
|
|
use math, only: math_Mandel3333to66, math_Voigt66to3333
|
|
|
|
use IO
|
|
|
|
use material
|
2012-02-21 22:01:37 +05:30
|
|
|
integer(pInt), intent(in) :: myFile
|
|
|
|
integer(pInt), parameter :: maxNchunks = 2_pInt
|
|
|
|
integer(pInt), dimension(1_pInt+2_pInt*maxNchunks) :: positions
|
|
|
|
integer(pInt) section, i, j, output, mySize
|
2013-01-28 22:06:26 +05:30
|
|
|
integer :: maxNinstance, k ! no pInt (stores a system dependen value from 'count'
|
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
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2013-01-09 03:41:59 +05:30
|
|
|
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) '<<<+- homogenization_',trim(homogenization_isostrain_label),' init -+>>>'
|
|
|
|
write(6,*) '$Id$'
|
2012-02-01 00:48:55 +05:30
|
|
|
#include "compilation_info.f90"
|
2013-01-09 03:41:59 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
maxNinstance = count(homogenization_type == homogenization_isostrain_label)
|
2012-02-21 22:01:37 +05:30
|
|
|
if (maxNinstance == 0) return
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
allocate(homogenization_isostrain_sizeState(maxNinstance)) ; homogenization_isostrain_sizeState = 0_pInt
|
|
|
|
allocate(homogenization_isostrain_sizePostResults(maxNinstance)); homogenization_isostrain_sizePostResults = 0_pInt
|
|
|
|
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput), &
|
|
|
|
maxNinstance)); homogenization_isostrain_sizePostResult = 0_pInt
|
|
|
|
allocate(homogenization_isostrain_Ngrains(maxNinstance)); homogenization_isostrain_Ngrains = 0_pInt
|
|
|
|
allocate(homogenization_isostrain_output(maxval(homogenization_Noutput), &
|
|
|
|
maxNinstance)) ; homogenization_isostrain_output = ''
|
|
|
|
|
2012-02-21 22:01:37 +05:30
|
|
|
rewind(myFile)
|
2012-02-13 19:48:07 +05:30
|
|
|
section = 0_pInt
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
do while (IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization) ! wind forward to <homogenization>
|
2012-02-21 22:01:37 +05:30
|
|
|
read(myFile,'(a1024)',END=100) line
|
2010-02-25 23:09:11 +05:30
|
|
|
enddo
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
do ! read thru sections of phase part
|
2012-02-21 22:01:37 +05:30
|
|
|
read(myFile,'(a1024)',END=100) line
|
2013-01-28 22:06:26 +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
|
2012-02-13 19:48:07 +05:30
|
|
|
section = section + 1_pInt
|
2013-01-28 22:06:26 +05:30
|
|
|
output = 0_pInt ! reset output counter
|
2010-02-25 23:09:11 +05:30
|
|
|
endif
|
2013-01-28 22:06:26 +05:30
|
|
|
if (section > 0 .and. homogenization_type(section) == homogenization_isostrain_label) then ! one of my sections
|
|
|
|
i = homogenization_typeInstance(section) ! which instance of my type is present homogenization
|
2010-02-25 23:09:11 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
2013-01-28 22:06:26 +05:30
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
|
2010-02-25 23:09:11 +05:30
|
|
|
select case(tag)
|
|
|
|
case ('(output)')
|
2012-02-13 19:48:07 +05:30
|
|
|
output = output + 1_pInt
|
|
|
|
homogenization_isostrain_output(output,i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
2010-02-25 23:09:11 +05:30
|
|
|
case ('ngrains')
|
2012-02-13 19:48:07 +05:30
|
|
|
homogenization_isostrain_Ngrains(i) = IO_intValue(line,positions,2_pInt)
|
2010-02-25 23:09:11 +05:30
|
|
|
end select
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
100 do k = 1,maxNinstance
|
2010-02-25 23:09:11 +05:30
|
|
|
homogenization_isostrain_sizeState(i) = 0_pInt
|
|
|
|
|
2012-02-21 22:01:37 +05:30
|
|
|
do j = 1_pInt,maxval(homogenization_Noutput)
|
2010-02-25 23:09:11 +05:30
|
|
|
select case(homogenization_isostrain_output(j,i))
|
|
|
|
case('ngrains')
|
2012-02-21 22:01:37 +05:30
|
|
|
mySize = 1_pInt
|
2010-02-25 23:09:11 +05:30
|
|
|
case default
|
2012-02-21 22:01:37 +05:30
|
|
|
mySize = 0_pInt
|
2010-02-25 23:09:11 +05:30
|
|
|
end select
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
if (mySize > 0_pInt) then ! any meaningful output found
|
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
|
|
|
homogenization_isostrain_sizePostResult(j,i) = mySize
|
|
|
|
homogenization_isostrain_sizePostResults(i) = &
|
|
|
|
homogenization_isostrain_sizePostResults(i) + mySize
|
2010-02-25 23:09:11 +05:30
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine homogenization_isostrain_init
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief sets the initial homogenization stated
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2010-02-25 23:09:11 +05:30
|
|
|
function homogenization_isostrain_stateInit(myInstance)
|
2013-01-28 22:06:26 +05:30
|
|
|
use prec, only: &
|
|
|
|
pReal
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(in) :: myInstance
|
|
|
|
real(pReal), dimension(homogenization_isostrain_sizeState(myInstance)) :: &
|
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
|
|
|
homogenization_isostrain_stateInit
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
homogenization_isostrain_stateInit = 0.0_pReal
|
|
|
|
|
2013-01-11 16:10:16 +05:30
|
|
|
end function homogenization_isostrain_stateInit
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief partitions the deformation gradient onto the constituents
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine homogenization_isostrain_partitionDeformation(F,F0,avgF,state,i,e)
|
|
|
|
use prec, only: pReal,p_vec
|
2012-02-21 22:01:37 +05:30
|
|
|
use mesh, only: mesh_element
|
2010-02-25 23:09:11 +05:30
|
|
|
use material, only: homogenization_maxNgrains,homogenization_Ngrains
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-01-28 22:06:26 +05:30
|
|
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F ! partioned def grad per grain
|
|
|
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: F0 ! initial partioned def grad per grain
|
|
|
|
real(pReal), dimension (3,3), intent(in) :: avgF ! my average def grad
|
|
|
|
type(p_vec), intent(in) :: state ! my state
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
i, & !< integration point number
|
|
|
|
e !< element number
|
|
|
|
|
|
|
|
F = spread(avgF,3,homogenization_Ngrains(mesh_element(3,e)))
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine homogenization_isostrain_partitionDeformation
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief update the internal state of the homogenization scheme and tell whether "done" and
|
|
|
|
! "happy" with result
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
function homogenization_isostrain_updateState(state,P,dPdF,i,e)
|
|
|
|
use prec, only: &
|
|
|
|
pReal,&
|
|
|
|
p_vec
|
|
|
|
use material, only: &
|
|
|
|
homogenization_maxNgrains
|
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-01-28 22:06:26 +05:30
|
|
|
type(p_vec), intent(inout) :: state !< my state
|
|
|
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P !< array of current grain stresses
|
|
|
|
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffnesses
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
i, & !< integration point number
|
|
|
|
e !< element number
|
2010-02-25 23:09:11 +05:30
|
|
|
logical, dimension(2) :: homogenization_isostrain_updateState
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
homogenization_isostrain_updateState = .true. ! homogenization at material point converged (done and happy)
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function homogenization_isostrain_updateState
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief derive average stress and stiffness from constituent quantities
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,i,e)
|
|
|
|
use prec, only: &
|
|
|
|
pReal
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_element
|
2010-02-25 23:09:11 +05:30
|
|
|
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-01-28 22:06:26 +05:30
|
|
|
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
|
|
|
|
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
|
|
|
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P !< array of current grain stresses
|
|
|
|
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffnesses
|
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
i, & !< integration point number
|
|
|
|
e !< element number
|
|
|
|
integer(pInt) :: Ngrains
|
|
|
|
|
|
|
|
Ngrains = homogenization_Ngrains(mesh_element(3,e))
|
2012-02-21 22:01:37 +05:30
|
|
|
avgP = sum(P,3)/real(Ngrains,pReal)
|
|
|
|
dAvgPdAvgF = sum(dPdF,5)/real(Ngrains,pReal)
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief derive average temperature from constituent quantities
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
real(pReal) pure function homogenization_isostrain_averageTemperature(Temperature,i,e)
|
|
|
|
use prec, only: &
|
|
|
|
pReal
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_element
|
|
|
|
use material, only: &
|
|
|
|
homogenization_maxNgrains, &
|
|
|
|
homogenization_Ngrains
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
|
|
|
real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature
|
2013-01-28 22:06:26 +05:30
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
i, & !< integration point number
|
|
|
|
e !< element number
|
|
|
|
integer(pInt) :: Ngrains
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
Ngrains = homogenization_Ngrains(mesh_element(3,e))
|
2012-02-21 22:01:37 +05:30
|
|
|
homogenization_isostrain_averageTemperature = sum(Temperature(1:Ngrains))/real(Ngrains,pReal)
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function homogenization_isostrain_averageTemperature
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief return array of homogenization results for post file inclusion
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function homogenization_isostrain_postResults(state,i,e)
|
|
|
|
use prec, only: &
|
|
|
|
pReal,&
|
|
|
|
p_vec
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_element
|
|
|
|
use material, only: &
|
|
|
|
homogenization_typeInstance, &
|
|
|
|
homogenization_Noutput
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
|
|
|
type(p_vec), intent(in) :: state
|
2013-01-28 22:06:26 +05:30
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
i, & !< integration point number
|
|
|
|
e !< element number
|
2012-03-09 01:55:28 +05:30
|
|
|
integer(pInt) :: homID,o,c
|
|
|
|
real(pReal), dimension(homogenization_isostrain_sizePostResults&
|
2013-01-28 22:06:26 +05:30
|
|
|
(homogenization_typeInstance(mesh_element(3,e)))) :: homogenization_isostrain_postResults
|
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
c = 0_pInt
|
2013-01-28 22:06:26 +05:30
|
|
|
homID = homogenization_typeInstance(mesh_element(3,e))
|
2010-02-25 23:09:11 +05:30
|
|
|
homogenization_isostrain_postResults = 0.0_pReal
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
do o = 1_pInt,homogenization_Noutput(mesh_element(3,e))
|
2010-02-25 23:09:11 +05:30
|
|
|
select case(homogenization_isostrain_output(o,homID))
|
|
|
|
case ('ngrains')
|
2012-02-21 22:01:37 +05:30
|
|
|
homogenization_isostrain_postResults(c+1_pInt) = real(homogenization_isostrain_Ngrains(homID),pReal)
|
|
|
|
c = c + 1_pInt
|
2010-02-25 23:09:11 +05:30
|
|
|
end select
|
|
|
|
enddo
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function homogenization_isostrain_postResults
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end module homogenization_isostrain
|