new (ph,me)-based data layout

This commit is contained in:
Martin Diehl 2020-12-29 07:34:25 +01:00
parent 7992ef474e
commit 22575b15ff
2 changed files with 33 additions and 27 deletions

View File

@ -48,13 +48,10 @@ module constitutive
real(pReal), dimension(:,:,:,:,:), allocatable :: & real(pReal), dimension(:,:,:,:,:), allocatable :: &
crystallite_F0, & !< def grad at start of FE inc crystallite_F0, & !< def grad at start of FE inc
crystallite_Fe, & !< current "elastic" def grad (end of converged time step) crystallite_Fe, & !< current "elastic" def grad (end of converged time step)
crystallite_Lp0, & !< plastic velocitiy grad at start of FE inc
crystallite_partitionedLp0, & !< plastic velocity grad at start of homog inc
crystallite_S0, & !< 2nd Piola-Kirchhoff stress vector at start of FE inc crystallite_S0, & !< 2nd Piola-Kirchhoff stress vector at start of FE inc
crystallite_partitionedS0 !< 2nd Piola-Kirchhoff stress vector at start of homog inc crystallite_partitionedS0 !< 2nd Piola-Kirchhoff stress vector at start of homog inc
real(pReal), dimension(:,:,:,:,:), allocatable, public :: & real(pReal), dimension(:,:,:,:,:), allocatable, public :: &
crystallite_P, & !< 1st Piola-Kirchhoff stress per grain crystallite_P, & !< 1st Piola-Kirchhoff stress per grain
crystallite_Lp, & !< current plastic velocitiy grad (end of converged time step)
crystallite_S, & !< current 2nd Piola-Kirchhoff stress vector (end of converged time step) crystallite_S, & !< current 2nd Piola-Kirchhoff stress vector (end of converged time step)
crystallite_partitionedF0, & !< def grad at start of homog inc crystallite_partitionedF0, & !< def grad at start of homog inc
crystallite_F !< def grad to be reached at end of homog inc crystallite_F !< def grad to be reached at end of homog inc
@ -65,14 +62,17 @@ module constitutive
type(tTensorContainer), dimension(:), allocatable :: & type(tTensorContainer), dimension(:), allocatable :: &
constitutive_mech_Fi, & constitutive_mech_Fi, &
constitutive_mech_Fi0, &
constitutive_mech_partitionedFi0, &
constitutive_mech_Li, &
constitutive_mech_Li0, &
constitutive_mech_partitionedLi0, &
constitutive_mech_Fp, & constitutive_mech_Fp, &
constitutive_mech_Li, &
constitutive_mech_Lp, &
constitutive_mech_Fi0, &
constitutive_mech_Fp0, & constitutive_mech_Fp0, &
constitutive_mech_partitionedFp0 constitutive_mech_Li0, &
constitutive_mech_Lp0, &
constitutive_mech_partitionedFi0, &
constitutive_mech_partitionedFp0, &
constitutive_mech_partitionedLi0, &
constitutive_mech_partitionedLp0
type :: tNumerics type :: tNumerics
@ -790,7 +790,6 @@ subroutine constitutive_forward
integer :: i, j integer :: i, j
crystallite_F0 = crystallite_F crystallite_F0 = crystallite_F
crystallite_Lp0 = crystallite_Lp
crystallite_S0 = crystallite_S crystallite_S0 = crystallite_S
call constitutive_mech_forward() call constitutive_mech_forward()
@ -864,12 +863,11 @@ subroutine crystallite_init
allocate(crystallite_F(3,3,cMax,iMax,eMax),source=0.0_pReal) allocate(crystallite_F(3,3,cMax,iMax,eMax),source=0.0_pReal)
allocate(crystallite_S0, & allocate(crystallite_S0, &
crystallite_F0,crystallite_Lp0, & crystallite_F0, &
crystallite_partitionedS0, & crystallite_partitionedS0, &
crystallite_partitionedF0,& crystallite_partitionedF0,&
crystallite_partitionedLp0, &
crystallite_S,crystallite_P, & crystallite_S,crystallite_P, &
crystallite_Fe,crystallite_Lp, & crystallite_Fe, &
source = crystallite_F) source = crystallite_F)
allocate(crystallite_orientation(cMax,iMax,eMax)) allocate(crystallite_orientation(cMax,iMax,eMax))
@ -917,6 +915,9 @@ subroutine crystallite_init
allocate(constitutive_mech_Li(phases%length)) allocate(constitutive_mech_Li(phases%length))
allocate(constitutive_mech_Li0(phases%length)) allocate(constitutive_mech_Li0(phases%length))
allocate(constitutive_mech_partitionedLi0(phases%length)) allocate(constitutive_mech_partitionedLi0(phases%length))
allocate(constitutive_mech_partitionedLp0(phases%length))
allocate(constitutive_mech_Lp0(phases%length))
allocate(constitutive_mech_Lp(phases%length))
do ph = 1, phases%length do ph = 1, phases%length
Nconstituents = count(material_phaseAt == ph) * discretization_nIPs Nconstituents = count(material_phaseAt == ph) * discretization_nIPs
@ -929,6 +930,9 @@ subroutine crystallite_init
allocate(constitutive_mech_Li(ph)%data(3,3,Nconstituents)) allocate(constitutive_mech_Li(ph)%data(3,3,Nconstituents))
allocate(constitutive_mech_Li0(ph)%data(3,3,Nconstituents)) allocate(constitutive_mech_Li0(ph)%data(3,3,Nconstituents))
allocate(constitutive_mech_partitionedLi0(ph)%data(3,3,Nconstituents)) allocate(constitutive_mech_partitionedLi0(ph)%data(3,3,Nconstituents))
allocate(constitutive_mech_partitionedLp0(ph)%data(3,3,Nconstituents))
allocate(constitutive_mech_Lp0(ph)%data(3,3,Nconstituents))
allocate(constitutive_mech_Lp(ph)%data(3,3,Nconstituents))
do so = 1, phase_Nsources(ph) do so = 1, phase_Nsources(ph)
allocate(sourceState(ph)%p(so)%subState0,source=sourceState(ph)%p(so)%state0) ! ToDo: hack allocate(sourceState(ph)%p(so)%subState0,source=sourceState(ph)%p(so)%state0) ! ToDo: hack
enddo enddo
@ -1000,7 +1004,6 @@ subroutine constitutive_initializeRestorationPoints(ip,el)
do co = 1,homogenization_Nconstituents(material_homogenizationAt(el)) do co = 1,homogenization_Nconstituents(material_homogenizationAt(el))
ph = material_phaseAt(co,el) ph = material_phaseAt(co,el)
me = material_phaseMemberAt(co,ip,el) me = material_phaseMemberAt(co,ip,el)
crystallite_partitionedLp0(1:3,1:3,co,ip,el) = crystallite_Lp0(1:3,1:3,co,ip,el)
crystallite_partitionedF0(1:3,1:3,co,ip,el) = crystallite_F0(1:3,1:3,co,ip,el) crystallite_partitionedF0(1:3,1:3,co,ip,el) = crystallite_F0(1:3,1:3,co,ip,el)
crystallite_partitionedS0(1:3,1:3,co,ip,el) = crystallite_S0(1:3,1:3,co,ip,el) crystallite_partitionedS0(1:3,1:3,co,ip,el) = crystallite_S0(1:3,1:3,co,ip,el)
@ -1033,7 +1036,6 @@ subroutine constitutive_windForward(ip,el)
ph = material_phaseAt(co,el) ph = material_phaseAt(co,el)
me = material_phaseMemberAt(co,ip,el) me = material_phaseMemberAt(co,ip,el)
crystallite_partitionedF0 (1:3,1:3,co,ip,el) = crystallite_F (1:3,1:3,co,ip,el) crystallite_partitionedF0 (1:3,1:3,co,ip,el) = crystallite_F (1:3,1:3,co,ip,el)
crystallite_partitionedLp0(1:3,1:3,co,ip,el) = crystallite_Lp(1:3,1:3,co,ip,el)
crystallite_partitionedS0 (1:3,1:3,co,ip,el) = crystallite_S (1:3,1:3,co,ip,el) crystallite_partitionedS0 (1:3,1:3,co,ip,el) = crystallite_S (1:3,1:3,co,ip,el)
call constitutive_mech_windForward(ph,me) call constitutive_mech_windForward(ph,me)
@ -1354,7 +1356,6 @@ subroutine crystallite_restartWrite
fileHandle = HDF5_openFile(fileName,'a') fileHandle = HDF5_openFile(fileName,'a')
call HDF5_write(fileHandle,crystallite_F,'F') call HDF5_write(fileHandle,crystallite_F,'F')
call HDF5_write(fileHandle,crystallite_Lp, 'L_p')
call HDF5_write(fileHandle,crystallite_S, 'S') call HDF5_write(fileHandle,crystallite_S, 'S')
groupHandle = HDF5_addGroup(fileHandle,'phase') groupHandle = HDF5_addGroup(fileHandle,'phase')
@ -1365,6 +1366,8 @@ subroutine crystallite_restartWrite
call HDF5_write(groupHandle,constitutive_mech_Fi(ph)%data,datasetName) call HDF5_write(groupHandle,constitutive_mech_Fi(ph)%data,datasetName)
write(datasetName,'(i0,a)') ph,'_L_i' write(datasetName,'(i0,a)') ph,'_L_i'
call HDF5_write(groupHandle,constitutive_mech_Li(ph)%data,datasetName) call HDF5_write(groupHandle,constitutive_mech_Li(ph)%data,datasetName)
write(datasetName,'(i0,a)') ph,'_L_p'
call HDF5_write(groupHandle,constitutive_mech_Lp(ph)%data,datasetName)
write(datasetName,'(i0,a)') ph,'_F_p' write(datasetName,'(i0,a)') ph,'_F_p'
call HDF5_write(groupHandle,constitutive_mech_Fp(ph)%data,datasetName) call HDF5_write(groupHandle,constitutive_mech_Fp(ph)%data,datasetName)
enddo enddo
@ -1398,7 +1401,6 @@ subroutine crystallite_restartRead
fileHandle = HDF5_openFile(fileName) fileHandle = HDF5_openFile(fileName)
call HDF5_read(fileHandle,crystallite_F0, 'F') call HDF5_read(fileHandle,crystallite_F0, 'F')
call HDF5_read(fileHandle,crystallite_Lp0,'L_p')
call HDF5_read(fileHandle,crystallite_S0, 'S') call HDF5_read(fileHandle,crystallite_S0, 'S')
groupHandle = HDF5_openGroup(fileHandle,'phase') groupHandle = HDF5_openGroup(fileHandle,'phase')
@ -1409,6 +1411,8 @@ subroutine crystallite_restartRead
call HDF5_read(groupHandle,constitutive_mech_Fi0(ph)%data,datasetName) call HDF5_read(groupHandle,constitutive_mech_Fi0(ph)%data,datasetName)
write(datasetName,'(i0,a)') ph,'_L_i' write(datasetName,'(i0,a)') ph,'_L_i'
call HDF5_read(groupHandle,constitutive_mech_Li0(ph)%data,datasetName) call HDF5_read(groupHandle,constitutive_mech_Li0(ph)%data,datasetName)
write(datasetName,'(i0,a)') ph,'_L_p'
call HDF5_read(groupHandle,constitutive_mech_Lp0(ph)%data,datasetName)
write(datasetName,'(i0,a)') ph,'_F_p' write(datasetName,'(i0,a)') ph,'_F_p'
call HDF5_read(groupHandle,constitutive_mech_Fp0(ph)%data,datasetName) call HDF5_read(groupHandle,constitutive_mech_Fp0(ph)%data,datasetName)
enddo enddo
@ -1442,7 +1446,7 @@ function constitutive_mech_getLp(co,ip,el) result(Lp)
integer, intent(in) :: co, ip, el integer, intent(in) :: co, ip, el
real(pReal), dimension(3,3) :: Lp real(pReal), dimension(3,3) :: Lp
Lp = crystallite_S(1:3,1:3,co,ip,el) Lp = constitutive_mech_Lp(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
end function constitutive_mech_getLp end function constitutive_mech_getLp

View File

@ -805,7 +805,7 @@ function integrateStress(F,subFp0,subFi0,Delta_t,co,ip,el) result(broken)
ph = material_phaseAt(co,el) ph = material_phaseAt(co,el)
me = material_phaseMemberAt(co,ip,el) me = material_phaseMemberAt(co,ip,el)
Lpguess = crystallite_Lp(1:3,1:3,co,ip,el) ! take as first guess Lpguess = constitutive_mech_Lp(ph)%data(1:3,1:3,me) ! take as first guess
Liguess = constitutive_mech_Li(ph)%data(1:3,1:3,me) ! take as first guess Liguess = constitutive_mech_Li(ph)%data(1:3,1:3,me) ! take as first guess
call math_invert33(invFp_current,devNull,error,subFp0) call math_invert33(invFp_current,devNull,error,subFp0)
@ -937,9 +937,9 @@ function integrateStress(F,subFp0,subFi0,Delta_t,co,ip,el) result(broken)
crystallite_P (1:3,1:3,co,ip,el) = matmul(matmul(F,invFp_new),matmul(S,transpose(invFp_new))) crystallite_P (1:3,1:3,co,ip,el) = matmul(matmul(F,invFp_new),matmul(S,transpose(invFp_new)))
crystallite_S (1:3,1:3,co,ip,el) = S crystallite_S (1:3,1:3,co,ip,el) = S
crystallite_Lp (1:3,1:3,co,ip,el) = Lpguess constitutive_mech_Lp(ph)%data(1:3,1:3,me) = Lpguess
constitutive_mech_Li(ph)%data(1:3,1:3,me) = Liguess constitutive_mech_Li(ph)%data(1:3,1:3,me) = Liguess
constitutive_mech_Fp(ph)%data(1:3,1:3,me) = Fp_new / math_det33(Fp_new)**(1.0_pReal/3.0_pReal) ! regularize constitutive_mech_Fp(ph)%data(1:3,1:3,me) = Fp_new / math_det33(Fp_new)**(1.0_pReal/3.0_pReal) ! regularize
constitutive_mech_Fi(ph)%data(1:3,1:3,me) = Fi_new constitutive_mech_Fi(ph)%data(1:3,1:3,me) = Fi_new
crystallite_Fe (1:3,1:3,co,ip,el) = matmul(matmul(F,invFp_new),invFi_new) crystallite_Fe (1:3,1:3,co,ip,el) = matmul(matmul(F,invFp_new),invFi_new)
broken = .false. broken = .false.
@ -1307,8 +1307,7 @@ subroutine crystallite_results(group,ph)
call results_writeDataset(group//'/mechanics/',constitutive_mech_Fi(ph)%data,output_constituent(ph)%label(ou),& call results_writeDataset(group//'/mechanics/',constitutive_mech_Fi(ph)%data,output_constituent(ph)%label(ou),&
'inelastic deformation gradient','1') 'inelastic deformation gradient','1')
case('L_p') case('L_p')
selected_tensors = select_tensors(crystallite_Lp,ph) call results_writeDataset(group//'/mechanics/',constitutive_mech_Lp(ph)%data,output_constituent(ph)%label(ou),&
call results_writeDataset(group//'/mechanics/',selected_tensors,output_constituent(ph)%label(ou),&
'plastic velocity gradient','1/s') 'plastic velocity gradient','1/s')
case('L_i') case('L_i')
call results_writeDataset(group//'/mechanics/',constitutive_mech_Li(ph)%data,output_constituent(ph)%label(ou),& call results_writeDataset(group//'/mechanics/',constitutive_mech_Li(ph)%data,output_constituent(ph)%label(ou),&
@ -1413,6 +1412,7 @@ module subroutine mech_initializeRestorationPoints(ph,me)
constitutive_mech_partitionedFi0(ph)%data(1:3,1:3,me) = constitutive_mech_Fi0(ph)%data(1:3,1:3,me) constitutive_mech_partitionedFi0(ph)%data(1:3,1:3,me) = constitutive_mech_Fi0(ph)%data(1:3,1:3,me)
constitutive_mech_partitionedFp0(ph)%data(1:3,1:3,me) = constitutive_mech_Fp0(ph)%data(1:3,1:3,me) constitutive_mech_partitionedFp0(ph)%data(1:3,1:3,me) = constitutive_mech_Fp0(ph)%data(1:3,1:3,me)
constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me) = constitutive_mech_Li0(ph)%data(1:3,1:3,me) constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me) = constitutive_mech_Li0(ph)%data(1:3,1:3,me)
constitutive_mech_partitionedLp0(ph)%data(1:3,1:3,me) = constitutive_mech_Lp0(ph)%data(1:3,1:3,me)
plasticState(ph)%partitionedState0(:,me) = plasticState(ph)%state0(:,me) plasticState(ph)%partitionedState0(:,me) = plasticState(ph)%state0(:,me)
end subroutine mech_initializeRestorationPoints end subroutine mech_initializeRestorationPoints
@ -1429,6 +1429,7 @@ module subroutine constitutive_mech_windForward(ph,me)
constitutive_mech_partitionedFp0(ph)%data(1:3,1:3,me) = constitutive_mech_Fp(ph)%data(1:3,1:3,me) constitutive_mech_partitionedFp0(ph)%data(1:3,1:3,me) = constitutive_mech_Fp(ph)%data(1:3,1:3,me)
constitutive_mech_partitionedFi0(ph)%data(1:3,1:3,me) = constitutive_mech_Fi(ph)%data(1:3,1:3,me) constitutive_mech_partitionedFi0(ph)%data(1:3,1:3,me) = constitutive_mech_Fi(ph)%data(1:3,1:3,me)
constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me) = constitutive_mech_Li(ph)%data(1:3,1:3,me) constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me) = constitutive_mech_Li(ph)%data(1:3,1:3,me)
constitutive_mech_partitionedLp0(ph)%data(1:3,1:3,me) = constitutive_mech_Lp(ph)%data(1:3,1:3,me)
plasticState(ph)%partitionedState0(:,me) = plasticState(ph)%state(:,me) plasticState(ph)%partitionedState0(:,me) = plasticState(ph)%state(:,me)
@ -1449,6 +1450,7 @@ module subroutine constitutive_mech_forward()
constitutive_mech_Fi0(ph) = constitutive_mech_Fi(ph) constitutive_mech_Fi0(ph) = constitutive_mech_Fi(ph)
constitutive_mech_Fp0(ph) = constitutive_mech_Fp(ph) constitutive_mech_Fp0(ph) = constitutive_mech_Fp(ph)
constitutive_mech_Li0(ph) = constitutive_mech_Li(ph) constitutive_mech_Li0(ph) = constitutive_mech_Li(ph)
constitutive_mech_Lp0(ph) = constitutive_mech_Lp(ph)
enddo enddo
end subroutine constitutive_mech_forward end subroutine constitutive_mech_forward
@ -1510,7 +1512,7 @@ module function crystallite_stress(dt,co,ip,el) result(converged_)
sizeDotState = plasticState(ph)%sizeDotState sizeDotState = plasticState(ph)%sizeDotState
subLi0 = constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me) subLi0 = constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me)
subLp0 = crystallite_partitionedLp0(1:3,1:3,co,ip,el) subLp0 = constitutive_mech_partitionedLp0(ph)%data(1:3,1:3,me)
subState0 = plasticState(ph)%partitionedState0(:,me) subState0 = plasticState(ph)%partitionedState0(:,me)
@ -1537,7 +1539,7 @@ module function crystallite_stress(dt,co,ip,el) result(converged_)
if (todo) then if (todo) then
subF0 = subF subF0 = subF
subLp0 = crystallite_Lp (1:3,1:3,co,ip,el) subLp0 = constitutive_mech_Lp(ph)%data(1:3,1:3,me)
subLi0 = constitutive_mech_Li(ph)%data(1:3,1:3,me) subLi0 = constitutive_mech_Li(ph)%data(1:3,1:3,me)
subFp0 = constitutive_mech_Fp(ph)%data(1:3,1:3,me) subFp0 = constitutive_mech_Fp(ph)%data(1:3,1:3,me)
subFi0 = constitutive_mech_Fi(ph)%data(1:3,1:3,me) subFi0 = constitutive_mech_Fi(ph)%data(1:3,1:3,me)
@ -1554,7 +1556,7 @@ module function crystallite_stress(dt,co,ip,el) result(converged_)
constitutive_mech_Fi(ph)%data(1:3,1:3,me) = subFi0 constitutive_mech_Fi(ph)%data(1:3,1:3,me) = subFi0
crystallite_S (1:3,1:3,co,ip,el) = crystallite_S0 (1:3,1:3,co,ip,el) crystallite_S (1:3,1:3,co,ip,el) = crystallite_S0 (1:3,1:3,co,ip,el)
if (subStep < 1.0_pReal) then ! actual (not initial) cutback if (subStep < 1.0_pReal) then ! actual (not initial) cutback
crystallite_Lp (1:3,1:3,co,ip,el) = subLp0 constitutive_mech_Lp(ph)%data(1:3,1:3,me) = subLp0
constitutive_mech_Li(ph)%data(1:3,1:3,me) = subLi0 constitutive_mech_Li(ph)%data(1:3,1:3,me) = subLi0
endif endif
plasticState(ph)%state(:,me) = subState0 plasticState(ph)%state(:,me) = subState0
@ -1600,7 +1602,7 @@ module subroutine mech_restore(ip,el,includeL)
ph = material_phaseAt(co,el) ph = material_phaseAt(co,el)
me = material_phaseMemberAt(co,ip,el) me = material_phaseMemberAt(co,ip,el)
if (includeL) then if (includeL) then
crystallite_Lp(1:3,1:3,co,ip,el) = crystallite_partitionedLp0(1:3,1:3,co,ip,el) constitutive_mech_Lp(ph)%data(1:3,1:3,me) = constitutive_mech_partitionedLp0(ph)%data(1:3,1:3,me)
constitutive_mech_Li(ph)%data(1:3,1:3,me) = constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me) constitutive_mech_Li(ph)%data(1:3,1:3,me) = constitutive_mech_partitionedLi0(ph)%data(1:3,1:3,me)
endif ! maybe protecting everything from overwriting makes more sense endif ! maybe protecting everything from overwriting makes more sense