doxygen comments for isostrain, unified naming ip->i, el->e
This commit is contained in:
parent
963ff0c3ae
commit
1594a4bdf8
|
@ -16,56 +16,49 @@
|
||||||
! You should have received a copy of the GNU General Public License
|
! You should have received a copy of the GNU General Public License
|
||||||
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
||||||
!
|
!
|
||||||
!##############################################################
|
!--------------------------------------------------------------------------------------------------
|
||||||
!* $Id$
|
! $Id$
|
||||||
!*****************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
!* Module: HOMOGENIZATION_ISOSTRAIN *
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!*****************************************************
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!* contains: *
|
!> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
|
||||||
!*****************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
||||||
! [isostrain]
|
|
||||||
! type isostrain
|
|
||||||
! Ngrains 6
|
|
||||||
! (output) Ngrains
|
|
||||||
|
|
||||||
module homogenization_isostrain
|
module homogenization_isostrain
|
||||||
|
use prec, only: &
|
||||||
use prec, only: pInt
|
pInt
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
character (len=*), parameter :: &
|
private
|
||||||
|
character (len=*), parameter, public :: &
|
||||||
homogenization_isostrain_label = 'isostrain'
|
homogenization_isostrain_label = 'isostrain'
|
||||||
|
|
||||||
integer(pInt),dimension(:), allocatable :: &
|
integer(pInt), dimension(:), allocatable, public :: &
|
||||||
homogenization_isostrain_sizeState, &
|
homogenization_isostrain_sizeState, &
|
||||||
homogenization_isostrain_Ngrains, &
|
|
||||||
homogenization_isostrain_sizePostResults
|
homogenization_isostrain_sizePostResults
|
||||||
|
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||||
integer(pInt), dimension(:,:), allocatable, target :: &
|
|
||||||
homogenization_isostrain_sizePostResult
|
homogenization_isostrain_sizePostResult
|
||||||
|
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||||
|
homogenization_isostrain_output !< name of each post result output
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target :: &
|
integer(pInt), dimension(:), allocatable, private :: &
|
||||||
homogenization_isostrain_output ! name of each post result output
|
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
|
||||||
|
|
||||||
contains
|
contains
|
||||||
!****************************************
|
|
||||||
!* - homogenization_isostrain_init
|
|
||||||
!* - homogenization_isostrain_stateInit
|
|
||||||
!* - homogenization_isostrain_deformationPartititon
|
|
||||||
!* - homogenization_isostrain_stateUpdate
|
|
||||||
!* - homogenization_isostrain_averageStressAndItsTangent
|
|
||||||
!* - homogenization_isostrain_postResults
|
|
||||||
!****************************************
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
!**************************************
|
!> @brief allocates all neccessary fields, reads information from material configuration file
|
||||||
!* Module initialization *
|
!--------------------------------------------------------------------------------------------------
|
||||||
!**************************************
|
subroutine homogenization_isostrain_init(myFile)
|
||||||
subroutine homogenization_isostrain_init(myFile) ! file pointer to material configuration
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||||
use prec, only: pInt
|
|
||||||
use math, only: math_Mandel3333to66, math_Voigt66to3333
|
use math, only: math_Mandel3333to66, math_Voigt66to3333
|
||||||
use IO
|
use IO
|
||||||
use material
|
use material
|
||||||
|
@ -124,10 +117,7 @@ subroutine homogenization_isostrain_init(myFile) ! fil
|
||||||
endif
|
endif
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
100 do k = 1,maxNinstance ! sanity checks
|
100 do k = 1,maxNinstance
|
||||||
enddo
|
|
||||||
|
|
||||||
do k = 1,maxNinstance
|
|
||||||
homogenization_isostrain_sizeState(i) = 0_pInt
|
homogenization_isostrain_sizeState(i) = 0_pInt
|
||||||
|
|
||||||
do j = 1_pInt,maxval(homogenization_Noutput)
|
do j = 1_pInt,maxval(homogenization_Noutput)
|
||||||
|
@ -149,11 +139,12 @@ subroutine homogenization_isostrain_init(myFile) ! fil
|
||||||
end subroutine homogenization_isostrain_init
|
end subroutine homogenization_isostrain_init
|
||||||
|
|
||||||
|
|
||||||
!*********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
!* initial homogenization state *
|
!> @brief sets the initial homogenization stated
|
||||||
!*********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
function homogenization_isostrain_stateInit(myInstance)
|
function homogenization_isostrain_stateInit(myInstance)
|
||||||
use prec, only: pReal,pInt
|
use prec, only: &
|
||||||
|
pReal
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), intent(in) :: myInstance
|
integer(pInt), intent(in) :: myInstance
|
||||||
|
@ -165,151 +156,132 @@ function homogenization_isostrain_stateInit(myInstance)
|
||||||
end function homogenization_isostrain_stateInit
|
end function homogenization_isostrain_stateInit
|
||||||
|
|
||||||
|
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
! partition material point def grad onto constituents
|
!> @brief partitions the deformation gradient onto the constituents
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine homogenization_isostrain_partitionDeformation(&
|
subroutine homogenization_isostrain_partitionDeformation(F,F0,avgF,state,i,e)
|
||||||
F, & ! partioned def grad per grain
|
use prec, only: pReal,p_vec
|
||||||
!
|
|
||||||
F0, & ! initial partioned def grad per grain
|
|
||||||
avgF, & ! my average def grad
|
|
||||||
state, & ! my state
|
|
||||||
ip, & ! my integration point
|
|
||||||
el & ! my element
|
|
||||||
)
|
|
||||||
use prec, only: pReal,pInt,p_vec
|
|
||||||
use mesh, only: mesh_element
|
use mesh, only: mesh_element
|
||||||
use material, only: homogenization_maxNgrains,homogenization_Ngrains
|
use material, only: homogenization_maxNgrains,homogenization_Ngrains
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F
|
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
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: F0 ! initial partioned def grad per grain
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF
|
real(pReal), dimension (3,3), intent(in) :: avgF ! my average def grad
|
||||||
type(p_vec), intent(in) :: state
|
type(p_vec), intent(in) :: state ! my state
|
||||||
integer(pInt), intent(in) :: ip,el
|
integer(pInt), intent(in) :: &
|
||||||
integer(pInt) i
|
i, & !< integration point number
|
||||||
|
e !< element number
|
||||||
|
|
||||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
F = spread(avgF,3,homogenization_Ngrains(mesh_element(3,e)))
|
||||||
forall (i = 1_pInt:homogenization_Ngrains(mesh_element(3,el))) &
|
|
||||||
F(1:3,1:3,i) = avgF
|
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_partitionDeformation
|
end subroutine homogenization_isostrain_partitionDeformation
|
||||||
|
|
||||||
|
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
! update the internal state of the homogenization scheme
|
!> @brief update the internal state of the homogenization scheme and tell whether "done" and
|
||||||
! and tell whether "done" and "happy" with result
|
! "happy" with result
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
function homogenization_isostrain_updateState(&
|
function homogenization_isostrain_updateState(state,P,dPdF,i,e)
|
||||||
state, & ! my state
|
use prec, only: &
|
||||||
!
|
pReal,&
|
||||||
P, & ! array of current grain stresses
|
p_vec
|
||||||
dPdF, & ! array of current grain stiffnesses
|
use material, only: &
|
||||||
ip, & ! my integration point
|
homogenization_maxNgrains
|
||||||
el & ! my element
|
|
||||||
)
|
|
||||||
|
|
||||||
use prec, only: pReal,pInt,p_vec
|
|
||||||
use material, only: homogenization_maxNgrains
|
|
||||||
implicit none
|
implicit none
|
||||||
|
type(p_vec), intent(inout) :: state !< my state
|
||||||
!* Definition of variables
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P !< array of current grain stresses
|
||||||
type(p_vec), intent(inout) :: state
|
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffnesses
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P
|
integer(pInt), intent(in) :: &
|
||||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF
|
i, & !< integration point number
|
||||||
integer(pInt), intent(in) :: ip,el
|
e !< element number
|
||||||
! integer(pInt) homID
|
|
||||||
logical, dimension(2) :: homogenization_isostrain_updateState
|
logical, dimension(2) :: homogenization_isostrain_updateState
|
||||||
|
|
||||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
|
||||||
homogenization_isostrain_updateState = .true. ! homogenization at material point converged (done and happy)
|
homogenization_isostrain_updateState = .true. ! homogenization at material point converged (done and happy)
|
||||||
|
|
||||||
end function homogenization_isostrain_updateState
|
end function homogenization_isostrain_updateState
|
||||||
|
|
||||||
|
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
! derive average stress and stiffness from constituent quantities
|
!> @brief derive average stress and stiffness from constituent quantities
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine homogenization_isostrain_averageStressAndItsTangent(&
|
subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,i,e)
|
||||||
avgP, & ! average stress at material point
|
use prec, only: &
|
||||||
dAvgPdAvgF, & ! average stiffness at material point
|
pReal
|
||||||
!
|
use mesh, only: &
|
||||||
P, & ! array of current grain stresses
|
mesh_element
|
||||||
dPdF, & ! array of current grain stiffnesses
|
|
||||||
ip, & ! my integration point
|
|
||||||
el & ! my element
|
|
||||||
)
|
|
||||||
|
|
||||||
use prec, only: pReal,pInt,p_vec
|
|
||||||
use mesh, only: mesh_element
|
|
||||||
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (3,3), intent(out) :: avgP
|
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
|
||||||
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF
|
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
|
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
|
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffnesses
|
||||||
integer(pInt), intent(in) :: ip,el
|
integer(pInt), intent(in) :: &
|
||||||
integer(pInt) Ngrains
|
i, & !< integration point number
|
||||||
|
e !< element number
|
||||||
|
integer(pInt) :: Ngrains
|
||||||
|
|
||||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
Ngrains = homogenization_Ngrains(mesh_element(3,e))
|
||||||
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
avgP = sum(P,3)/real(Ngrains,pReal)
|
avgP = sum(P,3)/real(Ngrains,pReal)
|
||||||
dAvgPdAvgF = sum(dPdF,5)/real(Ngrains,pReal)
|
dAvgPdAvgF = sum(dPdF,5)/real(Ngrains,pReal)
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
! derive average stress and stiffness from constituent quantities
|
!> @brief derive average temperature from constituent quantities
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
pure function homogenization_isostrain_averageTemperature(&
|
real(pReal) pure function homogenization_isostrain_averageTemperature(Temperature,i,e)
|
||||||
Temperature, & ! temperature
|
use prec, only: &
|
||||||
ip, & ! my integration point
|
pReal
|
||||||
el & ! my element
|
use mesh, only: &
|
||||||
)
|
mesh_element
|
||||||
|
use material, only: &
|
||||||
use prec, only: pReal,pInt,p_vec
|
homogenization_maxNgrains, &
|
||||||
use mesh, only: mesh_element
|
homogenization_Ngrains
|
||||||
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature
|
real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature
|
||||||
integer(pInt), intent(in) :: ip,el
|
integer(pInt), intent(in) :: &
|
||||||
real(pReal) homogenization_isostrain_averageTemperature
|
i, & !< integration point number
|
||||||
integer(pInt) Ngrains
|
e !< element number
|
||||||
|
integer(pInt) :: Ngrains
|
||||||
|
|
||||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
Ngrains = homogenization_Ngrains(mesh_element(3,e))
|
||||||
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
homogenization_isostrain_averageTemperature = sum(Temperature(1:Ngrains))/real(Ngrains,pReal)
|
homogenization_isostrain_averageTemperature = sum(Temperature(1:Ngrains))/real(Ngrains,pReal)
|
||||||
|
|
||||||
end function homogenization_isostrain_averageTemperature
|
end function homogenization_isostrain_averageTemperature
|
||||||
|
|
||||||
|
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
! return array of homogenization results for post file inclusion
|
!> @brief return array of homogenization results for post file inclusion
|
||||||
!********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
pure function homogenization_isostrain_postResults(&
|
pure function homogenization_isostrain_postResults(state,i,e)
|
||||||
state, & ! my state
|
use prec, only: &
|
||||||
ip, & ! my integration point
|
pReal,&
|
||||||
el & ! my element
|
p_vec
|
||||||
)
|
use mesh, only: &
|
||||||
|
mesh_element
|
||||||
use prec, only: pReal,pInt,p_vec
|
use material, only: &
|
||||||
use mesh, only: mesh_element
|
homogenization_typeInstance, &
|
||||||
use material, only: homogenization_typeInstance,homogenization_Noutput
|
homogenization_Noutput
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
type(p_vec), intent(in) :: state
|
type(p_vec), intent(in) :: state
|
||||||
integer(pInt), intent(in) :: ip,el
|
integer(pInt), intent(in) :: &
|
||||||
|
i, & !< integration point number
|
||||||
|
e !< element number
|
||||||
integer(pInt) :: homID,o,c
|
integer(pInt) :: homID,o,c
|
||||||
real(pReal), dimension(homogenization_isostrain_sizePostResults&
|
real(pReal), dimension(homogenization_isostrain_sizePostResults&
|
||||||
(homogenization_typeInstance(mesh_element(3,el)))) :: homogenization_isostrain_postResults
|
(homogenization_typeInstance(mesh_element(3,e)))) :: homogenization_isostrain_postResults
|
||||||
|
|
||||||
c = 0_pInt
|
c = 0_pInt
|
||||||
homID = homogenization_typeInstance(mesh_element(3,el))
|
homID = homogenization_typeInstance(mesh_element(3,e))
|
||||||
homogenization_isostrain_postResults = 0.0_pReal
|
homogenization_isostrain_postResults = 0.0_pReal
|
||||||
|
|
||||||
do o = 1_pInt,homogenization_Noutput(mesh_element(3,el))
|
do o = 1_pInt,homogenization_Noutput(mesh_element(3,e))
|
||||||
select case(homogenization_isostrain_output(o,homID))
|
select case(homogenization_isostrain_output(o,homID))
|
||||||
case ('ngrains')
|
case ('ngrains')
|
||||||
homogenization_isostrain_postResults(c+1_pInt) = real(homogenization_isostrain_Ngrains(homID),pReal)
|
homogenization_isostrain_postResults(c+1_pInt) = real(homogenization_isostrain_Ngrains(homID),pReal)
|
||||||
|
|
Loading…
Reference in New Issue