added int vec pointer for more efficient memory allocation of homog and micro counting (elemsOfHomogMicro) in material.f90
This commit is contained in:
parent
8f2e164fd2
commit
5b16f57727
|
@ -29,7 +29,8 @@
|
||||||
module material
|
module material
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pReal, &
|
pReal, &
|
||||||
pInt
|
pInt, &
|
||||||
|
p_intvec
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
@ -705,7 +706,7 @@ subroutine material_populateGrains
|
||||||
grain,constituentGrain,symExtension
|
grain,constituentGrain,symExtension
|
||||||
real(pReal) :: extreme,rnd
|
real(pReal) :: extreme,rnd
|
||||||
integer(pInt), dimension (:,:), allocatable :: Nelems ! counts number of elements in homog, micro array
|
integer(pInt), dimension (:,:), allocatable :: Nelems ! counts number of elements in homog, micro array
|
||||||
integer(pInt), dimension (:,:,:), allocatable :: elemsOfHomogMicro ! lists element number in homog, micro array
|
type(p_intvec), dimension (:,:), allocatable :: elemsOfHomogMicro ! lists element number in homog, micro array
|
||||||
|
|
||||||
myDebug = debug_level(debug_material)
|
myDebug = debug_level(debug_material)
|
||||||
|
|
||||||
|
@ -724,9 +725,15 @@ subroutine material_populateGrains
|
||||||
micro = mesh_element(4,e)
|
micro = mesh_element(4,e)
|
||||||
Nelems(homog,micro) = Nelems(homog,micro) + 1_pInt
|
Nelems(homog,micro) = Nelems(homog,micro) + 1_pInt
|
||||||
enddo
|
enddo
|
||||||
|
allocate(elemsOfHomogMicro(material_Nhomogenization,material_Nmicrostructure))
|
||||||
allocate(elemsOfHomogMicro(maxval(Nelems),material_Nhomogenization,material_Nmicrostructure))
|
do homog = 1,material_Nhomogenization
|
||||||
elemsOfHomogMicro = 0_pInt
|
do micro = 1,material_Nmicrostructure
|
||||||
|
if (Nelems(homog,micro) > 0_pInt) then
|
||||||
|
allocate(elemsOfHomogMicro(homog,micro)%p(Nelems(homog,micro)))
|
||||||
|
elemsOfHomogMicro(homog,micro)%p = 0_pInt
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! identify maximum grain count per IP (from element) and find grains per homog/micro pair
|
! identify maximum grain count per IP (from element) and find grains per homog/micro pair
|
||||||
|
@ -746,10 +753,9 @@ subroutine material_populateGrains
|
||||||
endif
|
endif
|
||||||
Ngrains(homog,micro) = Ngrains(homog,micro) + dGrains
|
Ngrains(homog,micro) = Ngrains(homog,micro) + dGrains
|
||||||
Nelems(homog,micro) = Nelems(homog,micro) + 1_pInt
|
Nelems(homog,micro) = Nelems(homog,micro) + 1_pInt
|
||||||
elemsOfHomogMicro(Nelems(homog,micro),homog,micro) = e ! remember elements active in this homog/micro pair
|
elemsOfHomogMicro(homog,micro)%p(Nelems(homog,micro)) = e ! remember elements active in this homog/micro pair
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
allocate(volumeOfGrain(maxval(Ngrains))) ! reserve memory for maximum case
|
allocate(volumeOfGrain(maxval(Ngrains))) ! reserve memory for maximum case
|
||||||
allocate(phaseOfGrain(maxval(Ngrains))) ! reserve memory for maximum case
|
allocate(phaseOfGrain(maxval(Ngrains))) ! reserve memory for maximum case
|
||||||
allocate(textureOfGrain(maxval(Ngrains))) ! reserve memory for maximum case
|
allocate(textureOfGrain(maxval(Ngrains))) ! reserve memory for maximum case
|
||||||
|
@ -780,7 +786,7 @@ subroutine material_populateGrains
|
||||||
volumeOfGrain = 0.0_pReal
|
volumeOfGrain = 0.0_pReal
|
||||||
grain = 0_pInt
|
grain = 0_pInt
|
||||||
do hme = 1_pInt, Nelems(homog,micro)
|
do hme = 1_pInt, Nelems(homog,micro)
|
||||||
e = elemsOfHomogMicro(hme,homog,micro) ! my combination of homog and micro, only perform calculations for elements with homog, micro combinations which is indexed in cpElemsindex
|
e = elemsOfHomogMicro(homog,micro)%p(hme) ! my combination of homog and micro, only perform calculations for elements with homog, micro combinations which is indexed in cpElemsindex
|
||||||
t = FE_geomtype(mesh_element(2,e))
|
t = FE_geomtype(mesh_element(2,e))
|
||||||
if (microstructure_elemhomo(micro)) then ! homogeneous distribution of grains over each element's IPs
|
if (microstructure_elemhomo(micro)) then ! homogeneous distribution of grains over each element's IPs
|
||||||
volumeOfGrain(grain+1_pInt:grain+dGrains) = sum(mesh_ipVolume(1:FE_Nips(t),e))/&
|
volumeOfGrain(grain+1_pInt:grain+dGrains) = sum(mesh_ipVolume(1:FE_Nips(t),e))/&
|
||||||
|
@ -900,7 +906,7 @@ subroutine material_populateGrains
|
||||||
! calc fraction after weighing with volumePerGrain, exchange in MC steps to improve result...
|
! calc fraction after weighing with volumePerGrain, exchange in MC steps to improve result...
|
||||||
grain = 0_pInt
|
grain = 0_pInt
|
||||||
do hme = 1_pInt, Nelems(homog,micro)
|
do hme = 1_pInt, Nelems(homog,micro)
|
||||||
e = elemsOfHomogMicro(hme,homog,micro) ! only perform calculations for elements with homog, micro combinations which is indexed in cpElemsindex
|
e = elemsOfHomogMicro(homog,micro)%p(hme) ! only perform calculations for elements with homog, micro combinations which is indexed in cpElemsindex
|
||||||
t = FE_geomtype(mesh_element(2,e))
|
t = FE_geomtype(mesh_element(2,e))
|
||||||
if (microstructure_elemhomo(micro)) then ! homogeneous distribution of grains over each element's IPs
|
if (microstructure_elemhomo(micro)) then ! homogeneous distribution of grains over each element's IPs
|
||||||
forall (i = 1_pInt:FE_Nips(t), g = 1_pInt:dGrains) ! loop over IPs and grains
|
forall (i = 1_pInt:FE_Nips(t), g = 1_pInt:dGrains) ! loop over IPs and grains
|
||||||
|
@ -930,6 +936,11 @@ subroutine material_populateGrains
|
||||||
deallocate(textureOfGrain)
|
deallocate(textureOfGrain)
|
||||||
deallocate(orientationOfGrain)
|
deallocate(orientationOfGrain)
|
||||||
deallocate(Nelems)
|
deallocate(Nelems)
|
||||||
|
!do homog = 1,material_Nhomogenization
|
||||||
|
! do micro = 1,material_Nmicrostructure
|
||||||
|
! if (Nelems(homog,micro) > 0_pInt) deallocate(elemsOfHomogMicro(homog,micro)%p) ! ToDo - causing segmentation fault: needs looking into
|
||||||
|
! enddo
|
||||||
|
!enddo
|
||||||
deallocate(elemsOfHomogMicro)
|
deallocate(elemsOfHomogMicro)
|
||||||
|
|
||||||
end subroutine material_populateGrains
|
end subroutine material_populateGrains
|
||||||
|
|
|
@ -70,6 +70,10 @@ module prec
|
||||||
real(pReal), dimension(:), pointer :: p
|
real(pReal), dimension(:), pointer :: p
|
||||||
end type p_vec
|
end type p_vec
|
||||||
|
|
||||||
|
type, public :: p_intvec
|
||||||
|
integer(pInt), dimension(:), pointer :: p
|
||||||
|
end type p_intvec
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
prec_init
|
prec_init
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue