This commit is contained in:
Martin Diehl 2019-12-10 17:52:37 +01:00
parent 74707b1b00
commit db91803b80
4 changed files with 3 additions and 126 deletions

@ -1 +1 @@
Subproject commit be78729525144accdbcda97e9abc625558af89cb
Subproject commit 952238b951a3d0c1c79df52530681724d3dead2e

View File

@ -16,8 +16,6 @@ module damage_local
implicit none
private
integer, dimension(:,:), allocatable, target, public :: &
damage_local_sizePostResult
character(len=64), dimension(:,:), allocatable, target, public :: &
damage_local_output
integer, dimension(:), allocatable, target, public :: &
@ -43,7 +41,6 @@ module damage_local
public :: &
damage_local_init, &
damage_local_updateState, &
damage_local_postResults, &
damage_local_Results
contains
@ -68,7 +65,6 @@ subroutine damage_local_init
maxNinstance = count(damage_type == DAMAGE_local_ID)
if (maxNinstance == 0) return
allocate(damage_local_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0)
allocate(damage_local_output (maxval(homogenization_Noutput),maxNinstance))
damage_local_output = ''
allocate(damage_local_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
@ -92,7 +88,6 @@ subroutine damage_local_init
case ('damage')
damage_local_output(i,damage_typeInstance(h)) = outputs(i)
damage_local_Noutput(instance) = damage_local_Noutput(instance) + 1
damage_local_sizePostResult(i,damage_typeInstance(h)) = 1
prm%outputID = [prm%outputID , damage_ID]
end select
@ -108,7 +103,6 @@ subroutine damage_local_init
! allocate state arrays
sizeState = 1
damageState(homog)%sizeState = sizeState
damageState(homog)%sizePostResults = sum(damage_local_sizePostResult(:,instance))
allocate(damageState(homog)%state0 (sizeState,NofMyHomog), source=damage_initialPhi(homog))
allocate(damageState(homog)%subState0(sizeState,NofMyHomog), source=damage_initialPhi(homog))
allocate(damageState(homog)%state (sizeState,NofMyHomog), source=damage_initialPhi(homog))
@ -239,36 +233,4 @@ subroutine damage_local_results(homog,group)
end subroutine damage_local_results
!--------------------------------------------------------------------------------------------------
!> @brief return array of damage results
!--------------------------------------------------------------------------------------------------
function damage_local_postResults(ip,el)
integer, intent(in) :: &
ip, & !< integration point
el !< element
real(pReal), dimension(sum(damage_local_sizePostResult(:,damage_typeInstance(material_homogenizationAt(el))))) :: &
damage_local_postResults
integer :: instance, homog, offset, o, c
homog = material_homogenizationAt(el)
offset = damageMapping(homog)%p(ip,el)
instance = damage_typeInstance(homog)
associate(prm => param(instance))
c = 0
outputsLoop: do o = 1,size(prm%outputID)
select case(prm%outputID(o))
case (damage_ID)
damage_local_postResults(c+1) = damage(homog)%p(offset)
c = c + 1
end select
enddo outputsLoop
end associate
end function damage_local_postResults
end module damage_local

View File

@ -19,8 +19,6 @@ module damage_nonlocal
implicit none
private
integer, dimension(:,:), allocatable, target, public :: &
damage_nonlocal_sizePostResult
character(len=64), dimension(:,:), allocatable, target, public :: &
damage_nonlocal_output
integer, dimension(:), allocatable, target, public :: &
@ -46,7 +44,6 @@ module damage_nonlocal
damage_nonlocal_getDiffusion33, &
damage_nonlocal_getMobility, &
damage_nonlocal_putNonLocalDamage, &
damage_nonlocal_postResults, &
damage_nonlocal_Results
contains
@ -71,7 +68,6 @@ subroutine damage_nonlocal_init
maxNinstance = count(damage_type == DAMAGE_nonlocal_ID)
if (maxNinstance == 0) return
allocate(damage_nonlocal_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0)
allocate(damage_nonlocal_output (maxval(homogenization_Noutput),maxNinstance))
damage_nonlocal_output = ''
allocate(damage_nonlocal_Noutput (maxNinstance), source=0)
@ -94,7 +90,6 @@ subroutine damage_nonlocal_init
case ('damage')
damage_nonlocal_output(i,damage_typeInstance(h)) = outputs(i)
damage_nonlocal_Noutput(instance) = damage_nonlocal_Noutput(instance) + 1
damage_nonlocal_sizePostResult(i,damage_typeInstance(h)) = 1
prm%outputID = [prm%outputID , damage_ID]
end select
@ -109,7 +104,6 @@ subroutine damage_nonlocal_init
! allocate state arrays
sizeState = 1
damageState(homog)%sizeState = sizeState
damageState(homog)%sizePostResults = sum(damage_nonlocal_sizePostResult(:,instance))
allocate(damageState(homog)%state0 (sizeState,NofMyHomog), source=damage_initialPhi(homog))
allocate(damageState(homog)%subState0(sizeState,NofMyHomog), source=damage_initialPhi(homog))
allocate(damageState(homog)%state (sizeState,NofMyHomog), source=damage_initialPhi(homog))
@ -248,7 +242,6 @@ subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
end subroutine damage_nonlocal_putNonLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file
!--------------------------------------------------------------------------------------------------
@ -275,37 +268,4 @@ subroutine damage_nonlocal_results(homog,group)
end subroutine damage_nonlocal_results
!--------------------------------------------------------------------------------------------------
!> @brief return array of damage results
!--------------------------------------------------------------------------------------------------
function damage_nonlocal_postResults(ip,el)
integer, intent(in) :: &
ip, & !< integration point
el !< element
real(pReal), dimension(sum(damage_nonlocal_sizePostResult(:,damage_typeInstance(material_homogenizationAt(el))))) :: &
damage_nonlocal_postResults
integer :: &
instance, homog, offset, o, c
homog = material_homogenizationAt(el)
offset = damageMapping(homog)%p(ip,el)
instance = damage_typeInstance(homog)
associate(prm => param(instance))
c = 0
outputsLoop: do o = 1,size(prm%outputID)
select case(prm%outputID(o))
case (damage_ID)
damage_nonlocal_postResults(c+1) = damage(homog)%p(offset)
c = c + 1
end select
enddo outputsLoop
end associate
end function damage_nonlocal_postResults
end module damage_nonlocal

View File

@ -39,8 +39,7 @@ module homogenization
materialpoint_results !< results array of material point
integer, public, protected :: &
materialpoint_sizeResults, &
thermal_maxSizePostResults, &
damage_maxSizePostResults
thermal_maxSizePostResults
real(pReal), dimension(:,:,:,:), allocatable :: &
materialpoint_subF0, & !< def grad of IP at beginning of homogenization increment
@ -196,35 +195,6 @@ subroutine homogenization_init
endif
endif
i = damage_typeInstance(p) ! which instance of this damage type
valid = .true. ! assume valid
select case(damage_type(p)) ! split per damage type
case (DAMAGE_none_ID)
outputName = DAMAGE_none_label
thisNoutput => null()
thisOutput => null()
thisSize => null()
case (DAMAGE_local_ID)
outputName = DAMAGE_local_label
thisNoutput => damage_local_Noutput
thisOutput => damage_local_output
thisSize => damage_local_sizePostResult
case (DAMAGE_nonlocal_ID)
outputName = DAMAGE_nonlocal_label
thisNoutput => damage_nonlocal_Noutput
thisOutput => damage_nonlocal_output
thisSize => damage_nonlocal_sizePostResult
case default
valid = .false.
end select
if (valid) then
write(FILEUNIT,'(a)') '(damage)'//char(9)//trim(outputName)
if (damage_type(p) /= DAMAGE_none_ID) then
do e = 1,thisNoutput(i)
write(FILEUNIT,'(a,i4)') trim(thisOutput(e,i))//char(9),thisSize(e,i)
enddo
endif
endif
endif
enddo
close(FILEUNIT)
@ -252,15 +222,12 @@ subroutine homogenization_init
!--------------------------------------------------------------------------------------------------
! allocate and initialize global state and postresutls variables
thermal_maxSizePostResults = 0
damage_maxSizePostResults = 0
do p = 1,size(config_homogenization)
thermal_maxSizePostResults = max(thermal_maxSizePostResults, thermalState(p)%sizePostResults)
damage_maxSizePostResults = max(damage_maxSizePostResults, damageState (p)%sizePostResults)
enddo
materialpoint_sizeResults = 1 & ! grain count
+ 1 + thermal_maxSizePostResults &
+ damage_maxSizePostResults &
+ homogenization_maxNgrains * 2 ! obsolete header information
allocate(materialpoint_results(materialpoint_sizeResults,discretization_nIP,discretization_nElem))
@ -742,8 +709,7 @@ function postResults(ip,el)
integer, intent(in) :: &
ip, & !< integration point
el !< element number
real(pReal), dimension( thermalState (material_homogenizationAt(el))%sizePostResults &
+ damageState (material_homogenizationAt(el))%sizePostResults) :: &
real(pReal), dimension( thermalState (material_homogenizationAt(el))%sizePostResults) :: &
postResults
integer :: &
startPos, endPos ,&
@ -766,17 +732,6 @@ function postResults(ip,el)
end select chosenThermal
startPos = endPos + 1
endPos = endPos + damageState(material_homogenizationAt(el))%sizePostResults
chosenDamage: select case (damage_type(material_homogenizationAt(el)))
case (DAMAGE_local_ID) chosenDamage
postResults(startPos:endPos) = damage_local_postResults(ip, el)
case (DAMAGE_nonlocal_ID) chosenDamage
postResults(startPos:endPos) = damage_nonlocal_postResults(ip, el)
end select chosenDamage
end function postResults