using newer interface
This commit is contained in:
parent
09c1150e3c
commit
53283d5c01
|
@ -728,7 +728,7 @@ subroutine crystallite_stressTangent
|
||||||
rhs_3333(1:3,1:3,o,p) = rhs_3333(1:3,1:3,o,p) &
|
rhs_3333(1:3,1:3,o,p) = rhs_3333(1:3,1:3,o,p) &
|
||||||
- crystallite_subdt(c,i,e)*matmul(invSubFi0,dLidS(1:3,1:3,o,p))
|
- crystallite_subdt(c,i,e)*matmul(invSubFi0,dLidS(1:3,1:3,o,p))
|
||||||
enddo; enddo
|
enddo; enddo
|
||||||
call math_invert2(temp_99,error,math_3333to99(lhs_3333))
|
call math_invert(temp_99,error,math_3333to99(lhs_3333))
|
||||||
if (error) then
|
if (error) then
|
||||||
call IO_warning(warning_ID=600,el=e,ip=i,g=c, &
|
call IO_warning(warning_ID=600,el=e,ip=i,g=c, &
|
||||||
ext_msg='inversion error in analytic tangent calculation')
|
ext_msg='inversion error in analytic tangent calculation')
|
||||||
|
@ -763,7 +763,7 @@ subroutine crystallite_stressTangent
|
||||||
lhs_3333 = crystallite_subdt(c,i,e)*math_mul3333xx3333(dSdFe,temp_3333) &
|
lhs_3333 = crystallite_subdt(c,i,e)*math_mul3333xx3333(dSdFe,temp_3333) &
|
||||||
+ math_mul3333xx3333(dSdFi,dFidS)
|
+ math_mul3333xx3333(dSdFi,dFidS)
|
||||||
|
|
||||||
call math_invert2(temp_99,error,math_identity2nd(9)+math_3333to99(lhs_3333))
|
call math_invert(temp_99,error,math_identity2nd(9)+math_3333to99(lhs_3333))
|
||||||
if (error) then
|
if (error) then
|
||||||
call IO_warning(warning_ID=600,el=e,ip=i,g=c, &
|
call IO_warning(warning_ID=600,el=e,ip=i,g=c, &
|
||||||
ext_msg='inversion error in analytic tangent calculation')
|
ext_msg='inversion error in analytic tangent calculation')
|
||||||
|
|
|
@ -423,7 +423,7 @@ subroutine utilities_updateGamma(C,saveReference)
|
||||||
A(1:3,1:3) = real(temp33_complex); A(4:6,4:6) = real(temp33_complex)
|
A(1:3,1:3) = real(temp33_complex); A(4:6,4:6) = real(temp33_complex)
|
||||||
A(1:3,4:6) = aimag(temp33_complex); A(4:6,1:3) = -aimag(temp33_complex)
|
A(1:3,4:6) = aimag(temp33_complex); A(4:6,1:3) = -aimag(temp33_complex)
|
||||||
if (abs(math_det33(A(1:3,1:3))) > 1e-16) then
|
if (abs(math_det33(A(1:3,1:3))) > 1e-16) then
|
||||||
call math_invert2(A_inv, err, A)
|
call math_invert(A_inv, err, A)
|
||||||
temp33_complex = cmplx(A_inv(1:3,1:3),A_inv(1:3,4:6),pReal)
|
temp33_complex = cmplx(A_inv(1:3,1:3),A_inv(1:3,4:6),pReal)
|
||||||
forall(l=1:3, m=1:3, n=1:3, o=1:3) &
|
forall(l=1:3, m=1:3, n=1:3, o=1:3) &
|
||||||
gamma_hat(l,m,n,o,i,j,k-grid3Offset) = temp33_complex(l,n)* &
|
gamma_hat(l,m,n,o,i,j,k-grid3Offset) = temp33_complex(l,n)* &
|
||||||
|
@ -534,7 +534,7 @@ subroutine utilities_fourierGammaConvolution(fieldAim)
|
||||||
A(1:3,1:3) = real(temp33_complex); A(4:6,4:6) = real(temp33_complex)
|
A(1:3,1:3) = real(temp33_complex); A(4:6,4:6) = real(temp33_complex)
|
||||||
A(1:3,4:6) = aimag(temp33_complex); A(4:6,1:3) = -aimag(temp33_complex)
|
A(1:3,4:6) = aimag(temp33_complex); A(4:6,1:3) = -aimag(temp33_complex)
|
||||||
if (abs(math_det33(A(1:3,1:3))) > 1e-16) then
|
if (abs(math_det33(A(1:3,1:3))) > 1e-16) then
|
||||||
call math_invert2(A_inv, err, A)
|
call math_invert(A_inv, err, A)
|
||||||
temp33_complex = cmplx(A_inv(1:3,1:3),A_inv(1:3,4:6),pReal)
|
temp33_complex = cmplx(A_inv(1:3,1:3),A_inv(1:3,4:6),pReal)
|
||||||
forall(l=1:3, m=1:3, n=1:3, o=1:3) &
|
forall(l=1:3, m=1:3, n=1:3, o=1:3) &
|
||||||
gamma_hat(l,m,n,o,1,1,1) = temp33_complex(l,n)*conjg(-xi1st(o,i,j,k))*xi1st(m,i,j,k)
|
gamma_hat(l,m,n,o,1,1,1) = temp33_complex(l,n)*conjg(-xi1st(o,i,j,k))*xi1st(m,i,j,k)
|
||||||
|
@ -730,7 +730,7 @@ function utilities_maskedCompliance(rot_BC,mask_stress,C)
|
||||||
c_reduced(k,j) = temp99_Real(n,m)
|
c_reduced(k,j) = temp99_Real(n,m)
|
||||||
endif; enddo; endif; enddo
|
endif; enddo; endif; enddo
|
||||||
|
|
||||||
call math_invert2(s_reduced, errmatinv, c_reduced) ! invert reduced stiffness
|
call math_invert(s_reduced, errmatinv, c_reduced) ! invert reduced stiffness
|
||||||
if (any(IEEE_is_NaN(s_reduced))) errmatinv = .true.
|
if (any(IEEE_is_NaN(s_reduced))) errmatinv = .true.
|
||||||
if (errmatinv) call IO_error(error_ID=400,ext_msg='utilities_maskedCompliance')
|
if (errmatinv) call IO_error(error_ID=400,ext_msg='utilities_maskedCompliance')
|
||||||
temp99_Real = 0.0_pReal ! fill up compliance with zeros
|
temp99_Real = 0.0_pReal ! fill up compliance with zeros
|
||||||
|
|
|
@ -597,7 +597,7 @@ module procedure mech_RGC_updateState
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! computing the update of the state variable (relaxation vectors) using the Jacobian matrix
|
! computing the update of the state variable (relaxation vectors) using the Jacobian matrix
|
||||||
allocate(jnverse(3*nIntFaceTot,3*nIntFaceTot),source=0.0_pReal)
|
allocate(jnverse(3*nIntFaceTot,3*nIntFaceTot),source=0.0_pReal)
|
||||||
call math_invert2(jnverse,error,jmatrix)
|
call math_invert(jnverse,error,jmatrix)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (iand(debug_level(debug_homogenization), debug_levelExtensive) /= 0) then
|
if (iand(debug_level(debug_homogenization), debug_levelExtensive) /= 0) then
|
||||||
|
|
10
src/math.f90
10
src/math.f90
|
@ -551,16 +551,16 @@ end function math_invSym3333
|
||||||
!> @brief invert quadratic matrix of arbitrary dimension
|
!> @brief invert quadratic matrix of arbitrary dimension
|
||||||
! ToDo: replaces math_invert
|
! ToDo: replaces math_invert
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine math_invert2(InvA, error, A)
|
subroutine math_invert(InvA, error, A)
|
||||||
|
|
||||||
real(pReal), dimension(:,:), intent(in) :: A
|
real(pReal), dimension(:,:), intent(in) :: A
|
||||||
|
|
||||||
real(pReal), dimension(size(A,1),size(A,1)), intent(out) :: invA
|
real(pReal), dimension(size(A,1),size(A,1)), intent(out) :: invA
|
||||||
logical, intent(out) :: error
|
logical, intent(out) :: error
|
||||||
|
|
||||||
call math_invert(size(A,1), A, InvA, error)
|
call math_invert2(size(A,1), A, InvA, error)
|
||||||
|
|
||||||
end subroutine math_invert2
|
end subroutine math_invert
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -568,7 +568,7 @@ end subroutine math_invert2
|
||||||
! ToDo: Wrong order of arguments and superfluous myDim argument.
|
! ToDo: Wrong order of arguments and superfluous myDim argument.
|
||||||
! Use math_invert2 instead
|
! Use math_invert2 instead
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine math_invert(myDim,A, InvA, error)
|
subroutine math_invert2(myDim,A, InvA, error)
|
||||||
|
|
||||||
integer, intent(in) :: myDim
|
integer, intent(in) :: myDim
|
||||||
real(pReal), dimension(myDim,myDim), intent(in) :: A
|
real(pReal), dimension(myDim,myDim), intent(in) :: A
|
||||||
|
@ -589,7 +589,7 @@ subroutine math_invert(myDim,A, InvA, error)
|
||||||
call dgetri(myDim,InvA,myDim,ipiv,work,myDim,ierr)
|
call dgetri(myDim,InvA,myDim,ipiv,work,myDim,ierr)
|
||||||
error = merge(.true.,.false., ierr /= 0)
|
error = merge(.true.,.false., ierr /= 0)
|
||||||
|
|
||||||
end subroutine math_invert
|
end subroutine math_invert2
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
Loading…
Reference in New Issue