lessons learned from compilation with Intel 2021.3
This commit is contained in:
parent
0651e242cf
commit
c2e86a2b2a
|
@ -766,25 +766,21 @@ end function relaxationVector
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief identify the normal of an interface
|
!> @brief identify the normal of an interface
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
pure function interfaceNormal(intFace,ho,en)
|
pure function interfaceNormal(intFace,ho,en) result(n)
|
||||||
|
|
||||||
real(pReal), dimension(3) :: interfaceNormal
|
|
||||||
|
|
||||||
|
real(pReal), dimension(3) :: n
|
||||||
integer, dimension(4), intent(in) :: intFace !< interface ID in 4D array (normal and position)
|
integer, dimension(4), intent(in) :: intFace !< interface ID in 4D array (normal and position)
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ho, &
|
ho, &
|
||||||
en
|
en
|
||||||
|
|
||||||
integer :: nPos
|
|
||||||
associate (dst => dependentState(ho))
|
associate (dst => dependentState(ho))
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
n = 0.0_pReal
|
||||||
! get the normal of the interface, identified from the value of intFace(1)
|
n(abs(intFace(1))) = real(intFace(1)/abs(intFace(1)),pReal) ! get the normal vector w.r.t. cluster axis
|
||||||
interfaceNormal = 0.0_pReal
|
|
||||||
nPos = abs(intFace(1)) ! identify the position of the interface in global state array
|
|
||||||
interfaceNormal(nPos) = real(intFace(1)/abs(intFace(1)),pReal) ! get the normal vector w.r.t. cluster axis
|
|
||||||
|
|
||||||
interfaceNormal = matmul(dst%orientation(1:3,1:3,en),interfaceNormal) ! map the normal vector into sample coordinate system (basis)
|
n = matmul(dst%orientation(1:3,1:3,en),n) ! map the normal vector into sample coordinate system (basis)
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
|
@ -794,22 +790,18 @@ end function interfaceNormal
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief collect six faces of a grain in 4D (normal and position)
|
!> @brief collect six faces of a grain in 4D (normal and position)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
pure function getInterface(iFace,iGrain3)
|
pure function getInterface(iFace,iGrain3) result(i)
|
||||||
|
|
||||||
integer, dimension(4) :: getInterface
|
|
||||||
|
|
||||||
|
integer, dimension(4) :: i
|
||||||
integer, dimension(3), intent(in) :: iGrain3 !< grain ID in 3D array
|
integer, dimension(3), intent(in) :: iGrain3 !< grain ID in 3D array
|
||||||
integer, intent(in) :: iFace !< face index (1..6) mapped like (-e1,-e2,-e3,+e1,+e2,+e3) or iDir = (-1,-2,-3,1,2,3)
|
integer, intent(in) :: iFace !< face index (1..6) mapped like (-e1,-e2,-e3,+e1,+e2,+e3) or iDir = (-1,-2,-3,1,2,3)
|
||||||
|
|
||||||
integer :: iDir !< direction of interface normal
|
integer :: iDir !< direction of interface normal
|
||||||
|
|
||||||
iDir = (int(real(iFace-1,pReal)/2.0_pReal)+1)*(-1)**iFace
|
|
||||||
getInterface(1) = iDir
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
iDir = (int(real(iFace-1,pReal)/2.0_pReal)+1)*(-1)**iFace
|
||||||
! identify the interface position by the direction of its normal
|
i = [iDir,iGrain3]
|
||||||
getInterface(2:4) = iGrain3
|
if (iDir < 0) i(1-iDir) = i(1-iDir)-1 ! to have a correlation with coordinate/position in real space
|
||||||
if (iDir < 0) getInterface(1-iDir) = getInterface(1-iDir)-1 ! to have a correlation with coordinate/position in real space
|
|
||||||
|
|
||||||
end function getInterface
|
end function getInterface
|
||||||
|
|
||||||
|
|
|
@ -67,8 +67,8 @@ module phase
|
||||||
interface
|
interface
|
||||||
|
|
||||||
! == cleaned:begin =================================================================================
|
! == cleaned:begin =================================================================================
|
||||||
module subroutine mechanical_init(materials,phases)
|
module subroutine mechanical_init(phases)
|
||||||
class(tNode), pointer :: materials,phases
|
class(tNode), pointer :: phases
|
||||||
end subroutine mechanical_init
|
end subroutine mechanical_init
|
||||||
|
|
||||||
module subroutine damage_init
|
module subroutine damage_init
|
||||||
|
@ -386,7 +386,7 @@ subroutine phase_init
|
||||||
phase_O(ph)%data = phase_O_0(ph)%data
|
phase_O(ph)%data = phase_O_0(ph)%data
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
call mechanical_init(materials,phases)
|
call mechanical_init(phases)
|
||||||
call damage_init
|
call damage_init
|
||||||
call thermal_init(phases)
|
call thermal_init(phases)
|
||||||
|
|
||||||
|
@ -482,7 +482,6 @@ end subroutine phase_results
|
||||||
subroutine crystallite_init()
|
subroutine crystallite_init()
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
ph, &
|
|
||||||
ce, &
|
ce, &
|
||||||
co, & !< counter in integration point component loop
|
co, & !< counter in integration point component loop
|
||||||
ip, & !< counter in integration point loop
|
ip, & !< counter in integration point loop
|
||||||
|
|
|
@ -199,10 +199,9 @@ contains
|
||||||
!> @brief Initialize mechanical field related constitutive models
|
!> @brief Initialize mechanical field related constitutive models
|
||||||
!> @details Initialize elasticity, plasticity and stiffness degradation models.
|
!> @details Initialize elasticity, plasticity and stiffness degradation models.
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine mechanical_init(materials,phases)
|
module subroutine mechanical_init(phases)
|
||||||
|
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
materials, &
|
|
||||||
phases
|
phases
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
|
|
|
@ -80,7 +80,7 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
||||||
|
|
||||||
logical, dimension(:), allocatable :: myPlasticity
|
logical, dimension(:), allocatable :: myPlasticity
|
||||||
integer :: &
|
integer :: &
|
||||||
ph, i, &
|
ph, &
|
||||||
Nmembers, &
|
Nmembers, &
|
||||||
sizeState, sizeDotState, &
|
sizeState, sizeDotState, &
|
||||||
startIndex, endIndex
|
startIndex, endIndex
|
||||||
|
|
|
@ -1119,8 +1119,11 @@ end subroutine nonlocal_dotState
|
||||||
!---------------------------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates the rate of change of microstructure
|
!> @brief calculates the rate of change of microstructure
|
||||||
!---------------------------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------------------------
|
||||||
|
#if __INTEL_COMPILER >= 2020
|
||||||
|
non_recursive function rhoDotFlux(timestep,ph,en,ip,el)
|
||||||
|
#else
|
||||||
function rhoDotFlux(timestep,ph,en,ip,el)
|
function rhoDotFlux(timestep,ph,en,ip,el)
|
||||||
|
#endif
|
||||||
real(pReal), intent(in) :: &
|
real(pReal), intent(in) :: &
|
||||||
timestep !< substepped crystallite time increment
|
timestep !< substepped crystallite time increment
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
|
|
|
@ -67,7 +67,6 @@ subroutine results_init(restart)
|
||||||
|
|
||||||
character(len=pPathLen) :: commandLine
|
character(len=pPathLen) :: commandLine
|
||||||
integer :: hdferr
|
integer :: hdferr
|
||||||
integer(HID_T) :: group_id
|
|
||||||
character(len=:), allocatable :: date
|
character(len=:), allocatable :: date
|
||||||
|
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue