Merge branch 'solver-cleanup' into 'development'
separate mechanics and thermal See merge request damask/DAMASK!890
This commit is contained in:
commit
19eaf4a27f
|
@ -158,9 +158,6 @@ subroutine materialpoint_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip,
|
||||||
else validCalculation
|
else validCalculation
|
||||||
call homogenization_mechanical_response(dt,(elCP-1)*discretization_nIPs + ip, &
|
call homogenization_mechanical_response(dt,(elCP-1)*discretization_nIPs + ip, &
|
||||||
(elCP-1)*discretization_nIPs + ip)
|
(elCP-1)*discretization_nIPs + ip)
|
||||||
if (.not. terminallyIll) &
|
|
||||||
call homogenization_mechanical_response2(dt,(elCP-1)*discretization_nIPs + ip, &
|
|
||||||
(elCP-1)*discretization_nIPs + ip)
|
|
||||||
|
|
||||||
terminalIllness: if (terminallyIll) then
|
terminalIllness: if (terminallyIll) then
|
||||||
|
|
||||||
|
|
|
@ -136,10 +136,6 @@ subroutine utilities_constitutiveResponse(P,P_av,C_volAvg,C_minmaxAvg,&
|
||||||
homogenization_F = reshape(F,[3,3,product(cells(1:2))*cells3]) ! set materialpoint target F to estimated field
|
homogenization_F = reshape(F,[3,3,product(cells(1:2))*cells3]) ! set materialpoint target F to estimated field
|
||||||
|
|
||||||
call homogenization_mechanical_response(Delta_t,1,product(cells(1:2))*cells3) ! calculate P field
|
call homogenization_mechanical_response(Delta_t,1,product(cells(1:2))*cells3) ! calculate P field
|
||||||
if (.not. terminallyIll) &
|
|
||||||
call homogenization_thermal_response(Delta_t,1,product(cells(1:2))*cells3)
|
|
||||||
if (.not. terminallyIll) &
|
|
||||||
call homogenization_mechanical_response2(Delta_t,1,product(cells(1:2))*cells3)
|
|
||||||
|
|
||||||
P = reshape(homogenization_P, [3,3,cells(1),cells(2),cells3])
|
P = reshape(homogenization_P, [3,3,cells(1),cells(2),cells3])
|
||||||
P_av = sum(sum(sum(P,dim=5),dim=4),dim=3) * wgt
|
P_av = sum(sum(sum(P,dim=5),dim=4),dim=3) * wgt
|
||||||
|
|
|
@ -323,6 +323,8 @@ subroutine formResidual(residual_subdomain,x_scal,r,dummy,err_PETSc)
|
||||||
real(pREAL), dimension(3,cells(1),cells(2),cells3) :: vectorField
|
real(pREAL), dimension(3,cells(1),cells(2),cells3) :: vectorField
|
||||||
|
|
||||||
|
|
||||||
|
call homogenization_thermal_response(Delta_t_,1,product(cells(1:2))*cells3)
|
||||||
|
|
||||||
associate(T => x_scal)
|
associate(T => x_scal)
|
||||||
vectorField = utilities_ScalarGradient(T)
|
vectorField = utilities_ScalarGradient(T)
|
||||||
ce = 0
|
ce = 0
|
||||||
|
|
|
@ -168,7 +168,6 @@ module homogenization
|
||||||
public :: &
|
public :: &
|
||||||
homogenization_init, &
|
homogenization_init, &
|
||||||
homogenization_mechanical_response, &
|
homogenization_mechanical_response, &
|
||||||
homogenization_mechanical_response2, &
|
|
||||||
homogenization_thermal_response, &
|
homogenization_thermal_response, &
|
||||||
homogenization_thermal_active, &
|
homogenization_thermal_active, &
|
||||||
homogenization_mu_T, &
|
homogenization_mu_T, &
|
||||||
|
@ -227,7 +226,8 @@ subroutine homogenization_mechanical_response(Delta_t,cell_start,cell_end)
|
||||||
doneAndHappy
|
doneAndHappy
|
||||||
|
|
||||||
|
|
||||||
!$OMP PARALLEL DO PRIVATE(en,ho,co,converged,doneAndHappy)
|
!$OMP PARALLEL
|
||||||
|
!$OMP DO PRIVATE(en,ho,co,converged,doneAndHappy)
|
||||||
do ce = cell_start, cell_end
|
do ce = cell_start, cell_end
|
||||||
|
|
||||||
en = material_entry_homogenization(ce)
|
en = material_entry_homogenization(ce)
|
||||||
|
@ -260,7 +260,18 @@ subroutine homogenization_mechanical_response(Delta_t,cell_start,cell_end)
|
||||||
terminallyIll = .true.
|
terminallyIll = .true.
|
||||||
end if
|
end if
|
||||||
end do
|
end do
|
||||||
!$OMP END PARALLEL DO
|
!$OMP END DO
|
||||||
|
|
||||||
|
!$OMP DO PRIVATE(ho)
|
||||||
|
do ce = cell_start, cell_end
|
||||||
|
ho = material_ID_homogenization(ce)
|
||||||
|
do co = 1, homogenization_Nconstituents(ho)
|
||||||
|
call crystallite_orientations(co,ce)
|
||||||
|
end do
|
||||||
|
call mechanical_homogenize(Delta_t,ce)
|
||||||
|
end do
|
||||||
|
!$OMP END DO
|
||||||
|
!$OMP END PARALLEL
|
||||||
|
|
||||||
end subroutine homogenization_mechanical_response
|
end subroutine homogenization_mechanical_response
|
||||||
|
|
||||||
|
@ -294,32 +305,6 @@ subroutine homogenization_thermal_response(Delta_t,cell_start,cell_end)
|
||||||
end subroutine homogenization_thermal_response
|
end subroutine homogenization_thermal_response
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine homogenization_mechanical_response2(Delta_t,cell_start,cell_end)
|
|
||||||
|
|
||||||
real(pREAL), intent(in) :: Delta_t !< time increment
|
|
||||||
integer, intent(in) :: &
|
|
||||||
cell_start, cell_end
|
|
||||||
|
|
||||||
integer :: &
|
|
||||||
co, ce, ho
|
|
||||||
|
|
||||||
|
|
||||||
!$OMP PARALLEL DO PRIVATE(ho)
|
|
||||||
do ce = cell_start, cell_end
|
|
||||||
ho = material_ID_homogenization(ce)
|
|
||||||
do co = 1, homogenization_Nconstituents(ho)
|
|
||||||
call crystallite_orientations(co,ce)
|
|
||||||
end do
|
|
||||||
call mechanical_homogenize(Delta_t,ce)
|
|
||||||
end do
|
|
||||||
!$OMP END PARALLEL DO
|
|
||||||
|
|
||||||
end subroutine homogenization_mechanical_response2
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief writes homogenization results to HDF5 output file
|
!> @brief writes homogenization results to HDF5 output file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
|
@ -18,6 +18,7 @@ module FEM_utilities
|
||||||
use math
|
use math
|
||||||
use misc
|
use misc
|
||||||
use IO
|
use IO
|
||||||
|
use parallelization
|
||||||
use discretization_mesh
|
use discretization_mesh
|
||||||
use homogenization
|
use homogenization
|
||||||
use FEM_quadrature
|
use FEM_quadrature
|
||||||
|
@ -144,16 +145,15 @@ subroutine utilities_constitutiveResponse(Delta_t,P_av,forwardData)
|
||||||
|
|
||||||
integer(MPI_INTEGER_KIND) :: err_MPI
|
integer(MPI_INTEGER_KIND) :: err_MPI
|
||||||
|
|
||||||
|
|
||||||
print'(/,1x,a)', '... evaluating constitutive response ......................................'
|
print'(/,1x,a)', '... evaluating constitutive response ......................................'
|
||||||
|
|
||||||
call homogenization_mechanical_response(Delta_t,1,mesh_maxNips*mesh_NcpElems) ! calculate P field
|
call homogenization_mechanical_response(Delta_t,1,mesh_maxNips*mesh_NcpElems) ! calculate P field
|
||||||
if (.not. terminallyIll) &
|
|
||||||
call homogenization_mechanical_response2(Delta_t,1,mesh_maxNips*mesh_NcpElems)
|
|
||||||
cutBack = .false.
|
cutBack = .false.
|
||||||
|
|
||||||
P_av = sum(homogenization_P,dim=3) * wgt
|
P_av = sum(homogenization_P,dim=3) * wgt
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,P_av,9_MPI_INTEGER_KIND,MPI_DOUBLE,MPI_SUM,MPI_COMM_WORLD,err_MPI)
|
call MPI_Allreduce(MPI_IN_PLACE,P_av,9_MPI_INTEGER_KIND,MPI_DOUBLE,MPI_SUM,MPI_COMM_WORLD,err_MPI)
|
||||||
if (err_MPI /= 0_MPI_INTEGER_KIND) error stop 'MPI error'
|
call parallelization_chkerr(err_MPI)
|
||||||
|
|
||||||
|
|
||||||
end subroutine utilities_constitutiveResponse
|
end subroutine utilities_constitutiveResponse
|
||||||
|
|
Loading…
Reference in New Issue