use centralized (and tested) funtionality

This commit is contained in:
Martin Diehl 2020-03-14 17:29:08 +01:00
parent 8bd708f3b1
commit 33aaa94865
6 changed files with 48 additions and 14 deletions

View File

@ -44,6 +44,7 @@ contains
subroutine IO_init subroutine IO_init
write(6,'(/,a)') ' <<<+- IO init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- IO init -+>>>'; flush(6)
call unitTest call unitTest
end subroutine IO_init end subroutine IO_init
@ -651,7 +652,7 @@ end function verifyFloatValue
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief check correctness of IO functions !> @brief check correctness of some IO functions
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine unitTest subroutine unitTest

View File

@ -502,15 +502,10 @@ subroutine lattice_init
lattice_C66(1:6,1:6,p) = applyLatticeSymmetryC66(lattice_C66(1:6,1:6,p),structure) lattice_C66(1:6,1:6,p) = applyLatticeSymmetryC66(lattice_C66(1:6,1:6,p),structure)
! (C11iso-C12iso)/2 with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5 lattice_mu(p) = equivalent_mu(lattice_C66(1:6,1:6,p),'voigt')
lattice_mu(p) = 0.2_pReal *(lattice_C66(1,1,p) -lattice_C66(1,2,p) +3.0_pReal*lattice_C66(4,4,p)) lattice_nu(p) = equivalent_nu(lattice_C66(1:6,1:6,p),'voigt')
! C12iso/(C11iso+C12iso) with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5
lattice_nu(p) = ( lattice_C66(1,1,p) +4.0_pReal*lattice_C66(1,2,p) -2.0_pReal*lattice_C66(4,4,p)) &
/ (4.0_pReal*lattice_C66(1,1,p) +6.0_pReal*lattice_C66(1,2,p) +2.0_pReal*lattice_C66(4,4,p))
lattice_C66(1:6,1:6,p) = math_sym3333to66(math_Voigt66to3333(lattice_C66(1:6,1:6,p))) ! Literature data is in Voigt notation lattice_C66(1:6,1:6,p) = math_sym3333to66(math_Voigt66to3333(lattice_C66(1:6,1:6,p))) ! Literature data is in Voigt notation
do i = 1, 6 do i = 1, 6
if (abs(lattice_C66(i,i,p))<tol_math_check) & if (abs(lattice_C66(i,i,p))<tol_math_check) &
call IO_error(135,el=i,ip=p,ext_msg='matrix diagonal "el"ement of phase "ip"') call IO_error(135,el=i,ip=p,ext_msg='matrix diagonal "el"ement of phase "ip"')
@ -534,6 +529,8 @@ subroutine lattice_init
lattice_DamageMobility(p) = config_phase(p)%getFloat('damage_mobility',defaultVal=0.0_pReal) lattice_DamageMobility(p) = config_phase(p)%getFloat('damage_mobility',defaultVal=0.0_pReal)
! SHOULD NOT BE PART OF LATTICE END ! SHOULD NOT BE PART OF LATTICE END
call unitTest
enddo enddo
end subroutine lattice_init end subroutine lattice_init
@ -2290,4 +2287,40 @@ function equivalent_mu(C,assumption) result(mu)
end function equivalent_mu end function equivalent_mu
!--------------------------------------------------------------------------------------------------
!> @brief check correctness of some lattice functions
!--------------------------------------------------------------------------------------------------
subroutine unitTest
real(pReal), dimension(:,:,:), allocatable :: CoSy
real(pReal), dimension(:,:), allocatable :: system
real(pReal), dimension(6,6) :: C
real(pReal), dimension(2) :: r
real(pReal) :: lambda
call random_number(r)
system = reshape([1.0_pReal+r(1),0.0_pReal,0.0_pReal, 0.0_pReal,1.0_pReal+r(2),0.0_pReal],[6,1])
CoSy = buildCoordinateSystem([1],[1],system,'fcc',0.0_pReal)
if(any(dNeq(CoSy(1:3,1:3,1),math_I3))) &
call IO_error(0)
call random_number(C)
C(1,1) = C(1,1) + 1.0_pReal
C = applyLatticeSymmetryC66(C,'iso')
if(dNeq(C(6,6),equivalent_mu(C,'voigt'),1.0e-12_pReal)) &
call IO_error(0,ext_msg='equivalent_mu/voigt')
if(dNeq(C(6,6),equivalent_mu(C,'voigt'),1.0e-12_pReal)) &
call IO_error(0,ext_msg='equivalent_mu/reuss')
lambda = C(1,2)
if(dNeq(lambda*0.5_pReal/(lambda+equivalent_mu(C,'voigt')),equivalent_nu(C,'voigt'),1.0e-12_pReal)) &
call IO_error(0,ext_msg='equivalent_nu/voigt')
if(dNeq(lambda*0.5_pReal/(lambda+equivalent_mu(C,'reuss')),equivalent_nu(C,'reuss'),1.0e-12_pReal)) &
call IO_error(0,ext_msg='equivalent_nu/reuss')
end subroutine unitTest
end module lattice end module lattice

View File

@ -1213,7 +1213,7 @@ end function math_clip
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief check correctness of (some) math functions !> @brief check correctness of some math functions
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine unitTest subroutine unitTest

View File

@ -241,7 +241,7 @@ end function cNeq
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief check correctness of (some) prec functions !> @brief check correctness of some prec functions
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine unitTest subroutine unitTest

View File

@ -455,7 +455,7 @@ end function inverse
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief check correctness of (some) quaternions functions !> @brief check correctness of some quaternions functions
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine unitTest subroutine unitTest

View File

@ -1222,7 +1222,7 @@ end function cu2ho
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief check correctness of (some) rotations functions !> @brief check correctness of some rotations functions
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine unitTest subroutine unitTest