Merge remote-tracking branch 'remotes/origin/42-new-coding-style-for-homogenization-NEW' into development

This commit is contained in:
Franz Roters 2019-01-28 15:51:34 +01:00
commit cf3efaaa02
5 changed files with 978 additions and 1344 deletions

View File

@ -45,10 +45,10 @@ module homogenization
materialpoint_stressAndItsTangent, & materialpoint_stressAndItsTangent, &
materialpoint_postResults materialpoint_postResults
private :: & private :: &
homogenization_partitionDeformation, & partitionDeformation, &
homogenization_updateState, & updateState, &
homogenization_averageStressAndItsTangent, & averageStressAndItsTangent, &
homogenization_postResults postResults
contains contains
@ -118,12 +118,9 @@ subroutine homogenization_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! parse homogenization from config file ! parse homogenization from config file
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) & if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call homogenization_none_init
call homogenization_none_init() if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call homogenization_isostrain_init
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) & if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call homogenization_RGC_init
call homogenization_isostrain_init(FILEUNIT)
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) &
call homogenization_RGC_init(FILEUNIT)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! parse thermal from config file ! parse thermal from config file
@ -156,17 +153,14 @@ subroutine homogenization_init
select case(homogenization_type(p)) ! split per homogenization type select case(homogenization_type(p)) ! split per homogenization type
case (HOMOGENIZATION_NONE_ID) case (HOMOGENIZATION_NONE_ID)
outputName = HOMOGENIZATION_NONE_label outputName = HOMOGENIZATION_NONE_label
thisNoutput => null()
thisOutput => null() thisOutput => null()
thisSize => null() thisSize => null()
case (HOMOGENIZATION_ISOSTRAIN_ID) case (HOMOGENIZATION_ISOSTRAIN_ID)
outputName = HOMOGENIZATION_ISOSTRAIN_label outputName = HOMOGENIZATION_ISOSTRAIN_label
thisNoutput => homogenization_isostrain_Noutput thisOutput => null()
thisOutput => homogenization_isostrain_output thisSize => null()
thisSize => homogenization_isostrain_sizePostResult
case (HOMOGENIZATION_RGC_ID) case (HOMOGENIZATION_RGC_ID)
outputName = HOMOGENIZATION_RGC_label outputName = HOMOGENIZATION_RGC_label
thisNoutput => homogenization_RGC_Noutput
thisOutput => homogenization_RGC_output thisOutput => homogenization_RGC_output
thisSize => homogenization_RGC_sizePostResult thisSize => homogenization_RGC_sizePostResult
case default case default
@ -176,8 +170,9 @@ subroutine homogenization_init
if (valid) then if (valid) then
write(FILEUNIT,'(a)') '(type)'//char(9)//trim(outputName) write(FILEUNIT,'(a)') '(type)'//char(9)//trim(outputName)
write(FILEUNIT,'(a,i4)') '(ngrains)'//char(9),homogenization_Ngrains(p) write(FILEUNIT,'(a,i4)') '(ngrains)'//char(9),homogenization_Ngrains(p)
if (homogenization_type(p) /= HOMOGENIZATION_NONE_ID) then if (homogenization_type(p) /= HOMOGENIZATION_NONE_ID .and. &
do e = 1,thisNoutput(i) homogenization_type(p) /= HOMOGENIZATION_ISOSTRAIN_ID) then
do e = 1,size(thisOutput(:,i))
write(FILEUNIT,'(a,i4)') trim(thisOutput(e,i))//char(9),thisSize(e,i) write(FILEUNIT,'(a,i4)') trim(thisOutput(e,i))//char(9),thisSize(e,i)
enddo enddo
endif endif
@ -605,7 +600,7 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
IpLooping2: do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) IpLooping2: do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e)
if ( materialpoint_requested(i,e) .and. & ! process requested but... if ( materialpoint_requested(i,e) .and. & ! process requested but...
.not. materialpoint_doneAndHappy(1,i,e)) then ! ...not yet done material points .not. materialpoint_doneAndHappy(1,i,e)) then ! ...not yet done material points
call homogenization_partitionDeformation(i,e) ! partition deformation onto constituents call partitionDeformation(i,e) ! partition deformation onto constituents
crystallite_dt(1:myNgrains,i,e) = materialpoint_subdt(i,e) ! propagate materialpoint dt to grains crystallite_dt(1:myNgrains,i,e) = materialpoint_subdt(i,e) ! propagate materialpoint dt to grains
crystallite_requested(1:myNgrains,i,e) = .true. ! request calculation for constituents crystallite_requested(1:myNgrains,i,e) = .true. ! request calculation for constituents
else else
@ -631,7 +626,7 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
if (.not. materialpoint_converged(i,e)) then if (.not. materialpoint_converged(i,e)) then
materialpoint_doneAndHappy(1:2,i,e) = [.true.,.false.] materialpoint_doneAndHappy(1:2,i,e) = [.true.,.false.]
else else
materialpoint_doneAndHappy(1:2,i,e) = homogenization_updateState(i,e) materialpoint_doneAndHappy(1:2,i,e) = updateState(i,e)
materialpoint_converged(i,e) = all(materialpoint_doneAndHappy(1:2,i,e)) ! converged if done and happy materialpoint_converged(i,e) = all(materialpoint_doneAndHappy(1:2,i,e)) ! converged if done and happy
endif endif
endif endif
@ -652,7 +647,7 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
!$OMP PARALLEL DO !$OMP PARALLEL DO
elementLooping4: do e = FEsolving_execElem(1),FEsolving_execElem(2) elementLooping4: do e = FEsolving_execElem(1),FEsolving_execElem(2)
IpLooping4: do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) IpLooping4: do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e)
call homogenization_averageStressAndItsTangent(i,e) call averageStressAndItsTangent(i,e)
enddo IpLooping4 enddo IpLooping4
enddo elementLooping4 enddo elementLooping4
!$OMP END PARALLEL DO !$OMP END PARALLEL DO
@ -710,7 +705,7 @@ subroutine materialpoint_postResults
thePos = thePos + 1_pInt thePos = thePos + 1_pInt
if (theSize > 0_pInt) then ! any homogenization results to mention? if (theSize > 0_pInt) then ! any homogenization results to mention?
materialpoint_results(thePos+1:thePos+theSize,i,e) = homogenization_postResults(i,e) ! tell homogenization results materialpoint_results(thePos+1:thePos+theSize,i,e) = postResults(i,e) ! tell homogenization results
thePos = thePos + theSize thePos = thePos + theSize
endif endif
@ -734,12 +729,12 @@ end subroutine materialpoint_postResults
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief partition material point def grad onto constituents !> @brief partition material point def grad onto constituents
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_partitionDeformation(ip,el) subroutine partitionDeformation(ip,el)
use mesh, only: & use mesh, only: &
mesh_element mesh_element
use material, only: & use material, only: &
homogenization_type, & homogenization_type, &
homogenization_maxNgrains, & homogenization_Ngrains, &
HOMOGENIZATION_NONE_ID, & HOMOGENIZATION_NONE_ID, &
HOMOGENIZATION_ISOSTRAIN_ID, & HOMOGENIZATION_ISOSTRAIN_ID, &
HOMOGENIZATION_RGC_ID HOMOGENIZATION_RGC_ID
@ -758,38 +753,36 @@ subroutine homogenization_partitionDeformation(ip,el)
chosenHomogenization: select case(homogenization_type(mesh_element(3,el))) chosenHomogenization: select case(homogenization_type(mesh_element(3,el)))
case (HOMOGENIZATION_NONE_ID) chosenHomogenization case (HOMOGENIZATION_NONE_ID) chosenHomogenization
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el) = 0.0_pReal crystallite_partionedF(1:3,1:3,1,ip,el) = materialpoint_subF(1:3,1:3,ip,el)
crystallite_partionedF(1:3,1:3,1:1,ip,el) = &
spread(materialpoint_subF(1:3,1:3,ip,el),3,1)
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
call homogenization_isostrain_partitionDeformation(& call homogenization_isostrain_partitionDeformation(&
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_partionedF(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
materialpoint_subF(1:3,1:3,ip,el),& materialpoint_subF(1:3,1:3,ip,el))
el)
case (HOMOGENIZATION_RGC_ID) chosenHomogenization case (HOMOGENIZATION_RGC_ID) chosenHomogenization
call homogenization_RGC_partitionDeformation(& call homogenization_RGC_partitionDeformation(&
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_partionedF(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
materialpoint_subF(1:3,1:3,ip,el),& materialpoint_subF(1:3,1:3,ip,el),&
ip, & ip, &
el) el)
end select chosenHomogenization end select chosenHomogenization
end subroutine homogenization_partitionDeformation end subroutine partitionDeformation
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief update the internal state of the homogenization scheme and tell whether "done" and !> @brief update the internal state of the homogenization scheme and tell whether "done" and
!> "happy" with result !> "happy" with result
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function homogenization_updateState(ip,el) function updateState(ip,el)
use mesh, only: & use mesh, only: &
mesh_element mesh_element
use material, only: & use material, only: &
homogenization_type, & homogenization_type, &
thermal_type, & thermal_type, &
damage_type, & damage_type, &
homogenization_maxNgrains, & homogenization_Ngrains, &
HOMOGENIZATION_RGC_ID, & HOMOGENIZATION_RGC_ID, &
THERMAL_adiabatic_ID, & THERMAL_adiabatic_ID, &
DAMAGE_local_ID DAMAGE_local_ID
@ -809,27 +802,27 @@ function homogenization_updateState(ip,el)
integer(pInt), intent(in) :: & integer(pInt), intent(in) :: &
ip, & !< integration point ip, & !< integration point
el !< element number el !< element number
logical, dimension(2) :: homogenization_updateState logical, dimension(2) :: updateState
homogenization_updateState = .true. updateState = .true.
chosenHomogenization: select case(homogenization_type(mesh_element(3,el))) chosenHomogenization: select case(homogenization_type(mesh_element(3,el)))
case (HOMOGENIZATION_RGC_ID) chosenHomogenization case (HOMOGENIZATION_RGC_ID) chosenHomogenization
homogenization_updateState = & updateState = &
homogenization_updateState .and. & updateState .and. &
homogenization_RGC_updateState(crystallite_P(1:3,1:3,1:homogenization_maxNgrains,ip,el), & homogenization_RGC_updateState(crystallite_P(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_partionedF(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
crystallite_partionedF0(1:3,1:3,1:homogenization_maxNgrains,ip,el),& crystallite_partionedF0(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el),&
materialpoint_subF(1:3,1:3,ip,el),& materialpoint_subF(1:3,1:3,ip,el),&
materialpoint_subdt(ip,el), & materialpoint_subdt(ip,el), &
crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
ip, & ip, &
el) el)
end select chosenHomogenization end select chosenHomogenization
chosenThermal: select case (thermal_type(mesh_element(3,el))) chosenThermal: select case (thermal_type(mesh_element(3,el)))
case (THERMAL_adiabatic_ID) chosenThermal case (THERMAL_adiabatic_ID) chosenThermal
homogenization_updateState = & updateState = &
homogenization_updateState .and. & updateState .and. &
thermal_adiabatic_updateState(materialpoint_subdt(ip,el), & thermal_adiabatic_updateState(materialpoint_subdt(ip,el), &
ip, & ip, &
el) el)
@ -837,25 +830,26 @@ function homogenization_updateState(ip,el)
chosenDamage: select case (damage_type(mesh_element(3,el))) chosenDamage: select case (damage_type(mesh_element(3,el)))
case (DAMAGE_local_ID) chosenDamage case (DAMAGE_local_ID) chosenDamage
homogenization_updateState = & updateState = &
homogenization_updateState .and. & updateState .and. &
damage_local_updateState(materialpoint_subdt(ip,el), & damage_local_updateState(materialpoint_subdt(ip,el), &
ip, & ip, &
el) el)
end select chosenDamage end select chosenDamage
end function homogenization_updateState end function updateState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief derive average stress and stiffness from constituent quantities !> @brief derive average stress and stiffness from constituent quantities
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_averageStressAndItsTangent(ip,el) subroutine averageStressAndItsTangent(ip,el)
use mesh, only: & use mesh, only: &
mesh_element mesh_element
use material, only: & use material, only: &
homogenization_type, & homogenization_type, &
homogenization_maxNgrains, & homogenization_typeInstance, &
homogenization_Ngrains, &
HOMOGENIZATION_NONE_ID, & HOMOGENIZATION_NONE_ID, &
HOMOGENIZATION_ISOSTRAIN_ID, & HOMOGENIZATION_ISOSTRAIN_ID, &
HOMOGENIZATION_RGC_ID HOMOGENIZATION_RGC_ID
@ -873,36 +867,39 @@ subroutine homogenization_averageStressAndItsTangent(ip,el)
chosenHomogenization: select case(homogenization_type(mesh_element(3,el))) chosenHomogenization: select case(homogenization_type(mesh_element(3,el)))
case (HOMOGENIZATION_NONE_ID) chosenHomogenization case (HOMOGENIZATION_NONE_ID) chosenHomogenization
materialpoint_P(1:3,1:3,ip,el) = sum(crystallite_P(1:3,1:3,1:1,ip,el),3) materialpoint_P(1:3,1:3,ip,el) = crystallite_P(1:3,1:3,1,ip,el)
materialpoint_dPdF(1:3,1:3,1:3,1:3,ip,el) & materialpoint_dPdF(1:3,1:3,1:3,1:3,ip,el) = crystallite_dPdF(1:3,1:3,1:3,1:3,1,ip,el)
= sum(crystallite_dPdF(1:3,1:3,1:3,1:3,1:1,ip,el),5)
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
call homogenization_isostrain_averageStressAndItsTangent(& call homogenization_isostrain_averageStressAndItsTangent(&
materialpoint_P(1:3,1:3,ip,el), & materialpoint_P(1:3,1:3,ip,el), &
materialpoint_dPdF(1:3,1:3,1:3,1:3,ip,el),& materialpoint_dPdF(1:3,1:3,1:3,1:3,ip,el),&
crystallite_P(1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_P(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
el) homogenization_typeInstance(mesh_element(3,el)))
case (HOMOGENIZATION_RGC_ID) chosenHomogenization case (HOMOGENIZATION_RGC_ID) chosenHomogenization
call homogenization_RGC_averageStressAndItsTangent(& call homogenization_RGC_averageStressAndItsTangent(&
materialpoint_P(1:3,1:3,ip,el), & materialpoint_P(1:3,1:3,ip,el), &
materialpoint_dPdF(1:3,1:3,1:3,1:3,ip,el),& materialpoint_dPdF(1:3,1:3,1:3,1:3,ip,el),&
crystallite_P(1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_P(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_maxNgrains,ip,el), & crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
el) homogenization_typeInstance(mesh_element(3,el)))
end select chosenHomogenization end select chosenHomogenization
end subroutine homogenization_averageStressAndItsTangent end subroutine averageStressAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief return array of homogenization results for post file inclusion. call only, !> @brief return array of homogenization results for post file inclusion. call only,
!> if homogenization_sizePostResults(i,e) > 0 !! !> if homogenization_sizePostResults(i,e) > 0 !!
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function homogenization_postResults(ip,el) function postResults(ip,el)
use mesh, only: & use mesh, only: &
mesh_element mesh_element
use material, only: & use material, only: &
material_homogenizationAt, &
homogenization_typeInstance,&
mappingHomogenization, & mappingHomogenization, &
homogState, & homogState, &
thermalState, & thermalState, &
@ -919,8 +916,6 @@ function homogenization_postResults(ip,el)
DAMAGE_none_ID, & DAMAGE_none_ID, &
DAMAGE_local_ID, & DAMAGE_local_ID, &
DAMAGE_nonlocal_ID DAMAGE_nonlocal_ID
use homogenization_isostrain, only: &
homogenization_isostrain_postResults
use homogenization_RGC, only: & use homogenization_RGC, only: &
homogenization_RGC_postResults homogenization_RGC_postResults
use thermal_adiabatic, only: & use thermal_adiabatic, only: &
@ -939,60 +934,46 @@ function homogenization_postResults(ip,el)
real(pReal), dimension( homogState (mappingHomogenization(2,ip,el))%sizePostResults & real(pReal), dimension( homogState (mappingHomogenization(2,ip,el))%sizePostResults &
+ thermalState (mappingHomogenization(2,ip,el))%sizePostResults & + thermalState (mappingHomogenization(2,ip,el))%sizePostResults &
+ damageState (mappingHomogenization(2,ip,el))%sizePostResults) :: & + damageState (mappingHomogenization(2,ip,el))%sizePostResults) :: &
homogenization_postResults postResults
integer(pInt) :: & integer(pInt) :: &
startPos, endPos startPos, endPos ,&
of, instance
homogenization_postResults = 0.0_pReal
postResults = 0.0_pReal
startPos = 1_pInt startPos = 1_pInt
endPos = homogState(mappingHomogenization(2,ip,el))%sizePostResults endPos = homogState(mappingHomogenization(2,ip,el))%sizePostResults
chosenHomogenization: select case (homogenization_type(mesh_element(3,el))) chosenHomogenization: select case (homogenization_type(mesh_element(3,el)))
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
homogenization_postResults(startPos:endPos) = &
homogenization_isostrain_postResults(&
ip, &
el, &
materialpoint_P(1:3,1:3,ip,el), &
materialpoint_F(1:3,1:3,ip,el))
case (HOMOGENIZATION_RGC_ID) chosenHomogenization case (HOMOGENIZATION_RGC_ID) chosenHomogenization
homogenization_postResults(startPos:endPos) = & instance = homogenization_typeInstance(material_homogenizationAt(el))
homogenization_RGC_postResults(& of = mappingHomogenization(1,ip,el)
ip, & postResults(startPos:endPos) = homogenization_RGC_postResults(instance,of)
el, &
materialpoint_P(1:3,1:3,ip,el), &
materialpoint_F(1:3,1:3,ip,el))
end select chosenHomogenization end select chosenHomogenization
startPos = endPos + 1_pInt startPos = endPos + 1_pInt
endPos = endPos + thermalState(mappingHomogenization(2,ip,el))%sizePostResults endPos = endPos + thermalState(mappingHomogenization(2,ip,el))%sizePostResults
chosenThermal: select case (thermal_type(mesh_element(3,el))) chosenThermal: select case (thermal_type(mesh_element(3,el)))
case (THERMAL_isothermal_ID) chosenThermal
case (THERMAL_adiabatic_ID) chosenThermal case (THERMAL_adiabatic_ID) chosenThermal
homogenization_postResults(startPos:endPos) = & postResults(startPos:endPos) = thermal_adiabatic_postResults(ip, el)
thermal_adiabatic_postResults(ip, el)
case (THERMAL_conduction_ID) chosenThermal case (THERMAL_conduction_ID) chosenThermal
homogenization_postResults(startPos:endPos) = & postResults(startPos:endPos) = thermal_conduction_postResults(ip, el)
thermal_conduction_postResults(ip, el)
end select chosenThermal end select chosenThermal
startPos = endPos + 1_pInt startPos = endPos + 1_pInt
endPos = endPos + damageState(mappingHomogenization(2,ip,el))%sizePostResults endPos = endPos + damageState(mappingHomogenization(2,ip,el))%sizePostResults
chosenDamage: select case (damage_type(mesh_element(3,el))) chosenDamage: select case (damage_type(mesh_element(3,el)))
case (DAMAGE_none_ID) chosenDamage
case (DAMAGE_local_ID) chosenDamage case (DAMAGE_local_ID) chosenDamage
homogenization_postResults(startPos:endPos) = & postResults(startPos:endPos) = damage_local_postResults(ip, el)
damage_local_postResults(ip, el)
case (DAMAGE_nonlocal_ID) chosenDamage case (DAMAGE_nonlocal_ID) chosenDamage
homogenization_postResults(startPos:endPos) = & postResults(startPos:endPos) = damage_nonlocal_postResults(ip, el)
damage_nonlocal_postResults(ip, el)
end select chosenDamage end select chosenDamage
end function homogenization_postResults end function postResults
end module homogenization end module homogenization

File diff suppressed because it is too large Load Diff

View File

@ -1,4 +1,5 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH !> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, 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 !> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
@ -6,220 +7,119 @@
module homogenization_isostrain module homogenization_isostrain
use prec, only: & use prec, only: &
pInt pInt
implicit none implicit none
private private
integer(pInt), dimension(:), allocatable, public, protected :: &
homogenization_isostrain_sizePostResults
integer(pInt), dimension(:,:), allocatable, target, public :: &
homogenization_isostrain_sizePostResult
character(len=64), dimension(:,:), allocatable, target, public :: &
homogenization_isostrain_output !< name of each post result output
integer(pInt), dimension(:), allocatable, target, public :: &
homogenization_isostrain_Noutput !< number of outputs per homog instance
integer(pInt), dimension(:), allocatable, private :: &
homogenization_isostrain_Ngrains
enum, bind(c) enum, bind(c)
enumerator :: undefined_ID, & enumerator :: &
nconstituents_ID, & parallel_ID, &
ipcoords_ID, & average_ID
avgdefgrad_ID, &
avgfirstpiola_ID
end enum end enum
enum, bind(c)
enumerator :: parallel_ID, &
average_ID
end enum
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
homogenization_isostrain_outputID !< ID of each post result output
integer(kind(average_ID)), dimension(:), allocatable, private :: &
homogenization_isostrain_mapping !< mapping type
type, private :: tParameters !< container type for internal constitutive parameters
integer(pInt) :: &
Nconstituents
integer(kind(average_ID)) :: &
mapping
end type
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
public :: & public :: &
homogenization_isostrain_init, & homogenization_isostrain_init, &
homogenization_isostrain_partitionDeformation, & homogenization_isostrain_partitionDeformation, &
homogenization_isostrain_averageStressAndItsTangent, & homogenization_isostrain_averageStressAndItsTangent
homogenization_isostrain_postResults
contains contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief allocates all neccessary fields, reads information from material configuration file !> @brief allocates all neccessary fields, reads information from material configuration file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_isostrain_init(fileUnit) subroutine homogenization_isostrain_init()
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800 #if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: & use, intrinsic :: iso_fortran_env, only: &
compiler_version, & compiler_version, &
compiler_options compiler_options
#endif #endif
use prec, only: &
pReal
use debug, only: & use debug, only: &
debug_HOMOGENIZATION, & debug_HOMOGENIZATION, &
debug_level, & debug_level, &
debug_levelBasic debug_levelBasic
use IO use IO, only: &
use material IO_timeStamp, &
use config IO_error
use material, only: &
homogenization_type, &
material_homog, &
homogState, &
HOMOGENIZATION_ISOSTRAIN_ID, &
HOMOGENIZATION_ISOSTRAIN_LABEL, &
homogenization_typeInstance
use config, only: &
config_homogenization
implicit none implicit none
integer(pInt), intent(in) :: fileUnit
integer(pInt), allocatable, dimension(:) :: chunkPos
integer(pInt) :: & integer(pInt) :: &
section = 0_pInt, i, mySize, o Ninstance, &
integer :: & h, &
maxNinstance, & NofMyHomog
homog, &
instance
integer :: &
NofMyHomog ! no pInt (stores a system dependen value from 'count'
character(len=65536) :: & character(len=65536) :: &
tag = '', & tag = ''
line = ''
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_ISOSTRAIN_label//' init -+>>>' write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_ISOSTRAIN_label//' init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp() write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90" #include "compilation_info.f90"
maxNinstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID) Ninstance = int(count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID),pInt)
if (maxNinstance == 0) return
if (iand(debug_level(debug_HOMOGENIZATION),debug_levelBasic) /= 0_pInt) & if (iand(debug_level(debug_HOMOGENIZATION),debug_levelBasic) /= 0_pInt) &
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
allocate(homogenization_isostrain_sizePostResults(maxNinstance), source=0_pInt)
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput),maxNinstance), & allocate(param(Ninstance)) ! one container of parameters per instance
source=0_pInt)
allocate(homogenization_isostrain_Noutput(maxNinstance), source=0_pInt) do h = 1_pInt, size(homogenization_type)
allocate(homogenization_isostrain_Ngrains(maxNinstance), source=0_pInt) if (homogenization_type(h) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
allocate(homogenization_isostrain_mapping(maxNinstance), source=average_ID)
allocate(homogenization_isostrain_output(maxval(homogenization_Noutput),maxNinstance)) associate(prm => param(homogenization_typeInstance(h)),&
homogenization_isostrain_output = '' config => config_homogenization(h))
allocate(homogenization_isostrain_outputID(maxval(homogenization_Noutput),maxNinstance), &
source=undefined_ID) prm%Nconstituents = config_homogenization(h)%getInt('nconstituents')
tag = 'sum'
select case(trim(config%getString('mapping',defaultVal = tag)))
case ('sum')
prm%mapping = parallel_ID
case ('avg')
prm%mapping = average_ID
case default
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
end select
NofMyHomog = count(material_homog == h)
homogState(h)%sizeState = 0_pInt
homogState(h)%sizePostResults = 0_pInt
allocate(homogState(h)%state0 (0_pInt,NofMyHomog))
allocate(homogState(h)%subState0(0_pInt,NofMyHomog))
allocate(homogState(h)%state (0_pInt,NofMyHomog))
end associate
rewind(fileUnit)
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
line = IO_read(fileUnit)
enddo enddo
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of homogenization part
line = IO_read(fileUnit)
if (IO_isBlank(line)) cycle ! skip empty lines
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
line = IO_read(fileUnit, .true.) ! reset IO_read
exit
endif
if (IO_getTag(line,'[',']') /= '') then ! next section
section = section + 1_pInt
cycle
endif
if (section > 0_pInt ) then ! do not short-circuit here (.and. with next if-statement). It's not safe in Fortran
if (homogenization_type(section) == HOMOGENIZATION_ISOSTRAIN_ID) then ! one of my sections
i = homogenization_typeInstance(section) ! which instance of my type is present homogenization
chunkPos = IO_stringPos(line)
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
select case(tag)
case ('(output)')
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
case('nconstituents','ngrains')
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = nconstituents_ID
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
case('ipcoords')
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = ipcoords_ID
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
case('avgdefgrad','avgf')
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = avgdefgrad_ID
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
case('avgp','avgfirstpiola','avg1stpiola')
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = avgfirstpiola_ID
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
end select
case ('nconstituents','ngrains')
homogenization_isostrain_Ngrains(i) = IO_intValue(line,chunkPos,2_pInt)
case ('mapping')
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
case ('parallel','sum')
homogenization_isostrain_mapping(i) = parallel_ID
case ('average','mean','avg')
homogenization_isostrain_mapping(i) = average_ID
case default
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
end select
end select
endif
endif
enddo parsingFile
initializeInstances: do homog = 1_pInt, material_Nhomogenization
myHomog: if (homogenization_type(homog) == HOMOGENIZATION_ISOSTRAIN_ID) then
NofMyHomog = count(material_homog == homog)
instance = homogenization_typeInstance(homog)
! * Determine size of postResults array
outputsLoop: do o = 1_pInt, homogenization_isostrain_Noutput(instance)
select case(homogenization_isostrain_outputID(o,instance))
case(nconstituents_ID)
mySize = 1_pInt
case(ipcoords_ID)
mySize = 3_pInt
case(avgdefgrad_ID, avgfirstpiola_ID)
mySize = 9_pInt
case default
mySize = 0_pInt
end select
outputFound: if (mySize > 0_pInt) then
homogenization_isostrain_sizePostResult(o,instance) = mySize
homogenization_isostrain_sizePostResults(instance) = &
homogenization_isostrain_sizePostResults(instance) + mySize
endif outputFound
enddo outputsLoop
! allocate state arrays
homogState(homog)%sizeState = 0_pInt
homogState(homog)%sizePostResults = homogenization_isostrain_sizePostResults(instance)
allocate(homogState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
allocate(homogState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
allocate(homogState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
endif myHomog
enddo initializeInstances
end subroutine homogenization_isostrain_init end subroutine homogenization_isostrain_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief partitions the deformation gradient onto the constituents !> @brief partitions the deformation gradient onto the constituents
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_isostrain_partitionDeformation(F,avgF,el) subroutine homogenization_isostrain_partitionDeformation(F,avgF)
use prec, only: & use prec, only: &
pReal pReal
use mesh, only: &
mesh_element
use material, only: &
homogenization_maxNgrains, &
homogenization_Ngrains
implicit none implicit none
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F !< partioned def grad per grain real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
real(pReal), dimension (3,3), intent(in) :: avgF !< my average def grad
integer(pInt), intent(in) :: & real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
el !< element number
F=0.0_pReal F = spread(avgF,3,size(F,3))
F(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)))= &
spread(avgF,3,homogenization_Ngrains(mesh_element(3,el)))
end subroutine homogenization_isostrain_partitionDeformation end subroutine homogenization_isostrain_partitionDeformation
@ -227,90 +127,31 @@ end subroutine homogenization_isostrain_partitionDeformation
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief derive average stress and stiffness from constituent quantities !> @brief derive average stress and stiffness from constituent quantities
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,el) subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,instance)
use prec, only: & use prec, only: &
pReal pReal
use mesh, only: &
mesh_element
use material, only: &
homogenization_maxNgrains, &
homogenization_Ngrains, &
homogenization_typeInstance
implicit none implicit none
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point 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,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) :: el !< element number
integer(pInt) :: &
homID, &
Ngrains
homID = homogenization_typeInstance(mesh_element(3,el)) real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses
Ngrains = homogenization_Ngrains(mesh_element(3,el)) real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
integer(pInt), intent(in) :: instance
select case (homogenization_isostrain_mapping(homID)) associate(prm => param(instance))
select case (prm%mapping)
case (parallel_ID) case (parallel_ID)
avgP = sum(P,3) avgP = sum(P,3)
dAvgPdAvgF = sum(dPdF,5) dAvgPdAvgF = sum(dPdF,5)
case (average_ID) case (average_ID)
avgP = sum(P,3) /real(Ngrains,pReal) avgP = sum(P,3) /real(prm%Nconstituents,pReal)
dAvgPdAvgF = sum(dPdF,5)/real(Ngrains,pReal) dAvgPdAvgF = sum(dPdF,5)/real(prm%Nconstituents,pReal)
end select end select
end associate
end subroutine homogenization_isostrain_averageStressAndItsTangent end subroutine homogenization_isostrain_averageStressAndItsTangent
!--------------------------------------------------------------------------------------------------
!> @brief return array of homogenization results for post file inclusion
!--------------------------------------------------------------------------------------------------
pure function homogenization_isostrain_postResults(ip,el,avgP,avgF)
use prec, only: &
pReal
use mesh, only: &
mesh_element, &
mesh_ipCoordinates
use material, only: &
homogenization_typeInstance, &
homogenization_Noutput
implicit none
integer(pInt), intent(in) :: &
ip, & !< integration point number
el !< element number
real(pReal), dimension(3,3), intent(in) :: &
avgP, & !< average stress at material point
avgF !< average deformation gradient at material point
real(pReal), dimension(homogenization_isostrain_sizePostResults &
(homogenization_typeInstance(mesh_element(3,el)))) :: &
homogenization_isostrain_postResults
integer(pInt) :: &
homID, &
o, c
c = 0_pInt
homID = homogenization_typeInstance(mesh_element(3,el))
homogenization_isostrain_postResults = 0.0_pReal
do o = 1_pInt,homogenization_Noutput(mesh_element(3,el))
select case(homogenization_isostrain_outputID(o,homID))
case (nconstituents_ID)
homogenization_isostrain_postResults(c+1_pInt) = real(homogenization_isostrain_Ngrains(homID),pReal)
c = c + 1_pInt
case (avgdefgrad_ID)
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(transpose(avgF),[9])
c = c + 9_pInt
case (avgfirstpiola_ID)
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(transpose(avgP),[9])
c = c + 9_pInt
case (ipcoords_ID)
homogenization_isostrain_postResults(c+1_pInt:c+3_pInt) = mesh_ipCoordinates(1:3,ip,el) ! current ip coordinates
c = c + 3_pInt
end select
enddo
end function homogenization_isostrain_postResults
end module homogenization_isostrain end module homogenization_isostrain

View File

@ -2,7 +2,7 @@
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH !> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH !> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH !> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief dummy homogenization homogenization scheme !> @brief dummy homogenization homogenization scheme for 1 constituent per material point
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module homogenization_none module homogenization_none
@ -24,35 +24,46 @@ subroutine homogenization_none_init()
compiler_options compiler_options
#endif #endif
use prec, only: & use prec, only: &
pReal, & pInt
pInt use debug, only: &
debug_HOMOGENIZATION, &
debug_level, &
debug_levelBasic
use IO, only: & use IO, only: &
IO_timeStamp IO_timeStamp
use material
use config use material, only: &
homogenization_type, &
material_homog, &
homogState, &
HOMOGENIZATION_NONE_LABEL, &
HOMOGENIZATION_NONE_ID
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &
homog, & Ninstance, &
h, &
NofMyHomog NofMyHomog
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_NONE_label//' init -+>>>' write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_NONE_label//' init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp() write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90" #include "compilation_info.f90"
initializeInstances: do homog = 1_pInt, material_Nhomogenization Ninstance = int(count(homogenization_type == HOMOGENIZATION_NONE_ID),pInt)
if (iand(debug_level(debug_HOMOGENIZATION),debug_levelBasic) /= 0_pInt) &
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
do h = 1_pInt, size(homogenization_type)
if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
myhomog: if (homogenization_type(homog) == HOMOGENIZATION_none_ID) then NofMyHomog = count(material_homog == h)
NofMyHomog = count(material_homog == homog) homogState(h)%sizeState = 0_pInt
homogState(homog)%sizeState = 0_pInt homogState(h)%sizePostResults = 0_pInt
homogState(homog)%sizePostResults = 0_pInt allocate(homogState(h)%state0 (0_pInt,NofMyHomog))
allocate(homogState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal) allocate(homogState(h)%subState0(0_pInt,NofMyHomog))
allocate(homogState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal) allocate(homogState(h)%state (0_pInt,NofMyHomog))
allocate(homogState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
endif myhomog
enddo initializeInstances
enddo
end subroutine homogenization_none_init end subroutine homogenization_none_init

View File

@ -1998,6 +1998,7 @@ end function math_symmetricEulers
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief eigenvalues and eigenvectors of symmetric matrix m !> @brief eigenvalues and eigenvectors of symmetric matrix m
! ToDo: has wrong oder of arguments
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine math_eigenValuesVectorsSym(m,values,vectors,error) subroutine math_eigenValuesVectorsSym(m,values,vectors,error)
@ -2021,9 +2022,10 @@ end subroutine math_eigenValuesVectorsSym
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief eigenvalues and eigenvectors of symmetric 33 matrix m using an analytical expression !> @brief eigenvalues and eigenvectors of symmetric 33 matrix m using an analytical expression
!> and the general LAPACK powered version for arbritrary sized matrices as fallback !> and the general LAPACK powered version for arbritrary sized matrices as fallback
!> @author Joachim Kopp, MaxPlanckInstitut für Kernphysik, Heidelberg (Copyright (C) 2006) !> @author Joachim Kopp, Max-Planck-Institut für Kernphysik, Heidelberg (Copyright (C) 2006)
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH !> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @details See http://arxiv.org/abs/physics/0610206 (DSYEVH3) !> @details See http://arxiv.org/abs/physics/0610206 (DSYEVH3)
! ToDo: has wrong oder of arguments
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine math_eigenValuesVectorsSym33(m,values,vectors) subroutine math_eigenValuesVectorsSym33(m,values,vectors)