preparing for PGI compiler
This commit is contained in:
parent
43ead134d2
commit
453eb538f7
|
@ -36,6 +36,10 @@ add_library(IO OBJECT "IO.f90")
|
||||||
add_dependencies(IO DAMASK_INTERFACE)
|
add_dependencies(IO DAMASK_INTERFACE)
|
||||||
list(APPEND OBJECTFILES $<TARGET_OBJECTS:IO>)
|
list(APPEND OBJECTFILES $<TARGET_OBJECTS:IO>)
|
||||||
|
|
||||||
|
add_library(FUTURE OBJECT "future.f90")
|
||||||
|
add_dependencies(FUTURE IO)
|
||||||
|
list(APPEND OBJECTFILES $<TARGET_OBJECTS:FUTURE>)
|
||||||
|
|
||||||
add_library(NUMERICS OBJECT "numerics.f90")
|
add_library(NUMERICS OBJECT "numerics.f90")
|
||||||
add_dependencies(NUMERICS IO)
|
add_dependencies(NUMERICS IO)
|
||||||
list(APPEND OBJECTFILES $<TARGET_OBJECTS:NUMERICS>)
|
list(APPEND OBJECTFILES $<TARGET_OBJECTS:NUMERICS>)
|
||||||
|
|
|
@ -42,6 +42,7 @@ module Lambert
|
||||||
pReal
|
pReal
|
||||||
use math, only: &
|
use math, only: &
|
||||||
PI
|
PI
|
||||||
|
use future
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
|
@ -18,6 +18,7 @@ module crystallite
|
||||||
FEsolving_execIP
|
FEsolving_execIP
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_Ngrains
|
homogenization_Ngrains
|
||||||
|
use future
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
|
@ -352,7 +353,7 @@ subroutine crystallite_init
|
||||||
crystallite_F0(1:3,1:3,c,i,e) = math_I3
|
crystallite_F0(1:3,1:3,c,i,e) = math_I3
|
||||||
crystallite_localPlasticity(c,i,e) = phase_localPlasticity(material_phase(c,i,e))
|
crystallite_localPlasticity(c,i,e) = phase_localPlasticity(material_phase(c,i,e))
|
||||||
crystallite_Fe(1:3,1:3,c,i,e) = math_inv33(matmul(crystallite_Fi0(1:3,1:3,c,i,e), &
|
crystallite_Fe(1:3,1:3,c,i,e) = math_inv33(matmul(crystallite_Fi0(1:3,1:3,c,i,e), &
|
||||||
crystallite_Fp0(1:3,1:3,c,i,e))) ! assuming that euler angles are given in internal strain free configuration
|
crystallite_Fp0(1:3,1:3,c,i,e))) ! assuming that euler angles are given in internal strain free configuration
|
||||||
crystallite_Fp(1:3,1:3,c,i,e) = crystallite_Fp0(1:3,1:3,c,i,e)
|
crystallite_Fp(1:3,1:3,c,i,e) = crystallite_Fp0(1:3,1:3,c,i,e)
|
||||||
crystallite_Fi(1:3,1:3,c,i,e) = crystallite_Fi0(1:3,1:3,c,i,e)
|
crystallite_Fi(1:3,1:3,c,i,e) = crystallite_Fi0(1:3,1:3,c,i,e)
|
||||||
crystallite_requested(c,i,e) = .true.
|
crystallite_requested(c,i,e) = .true.
|
||||||
|
@ -600,8 +601,8 @@ function crystallite_stress(dummyArgumentToPreventInternalCompilerErrorWithGCC)
|
||||||
+ crystallite_subStep(c,i,e) * (crystallite_partionedF (1:3,1:3,c,i,e) &
|
+ crystallite_subStep(c,i,e) * (crystallite_partionedF (1:3,1:3,c,i,e) &
|
||||||
- crystallite_partionedF0(1:3,1:3,c,i,e))
|
- crystallite_partionedF0(1:3,1:3,c,i,e))
|
||||||
crystallite_Fe(1:3,1:3,c,i,e) = matmul(matmul(crystallite_subF (1:3,1:3,c,i,e), &
|
crystallite_Fe(1:3,1:3,c,i,e) = matmul(matmul(crystallite_subF (1:3,1:3,c,i,e), &
|
||||||
crystallite_invFp(1:3,1:3,c,i,e)), &
|
crystallite_invFp(1:3,1:3,c,i,e)), &
|
||||||
crystallite_invFi(1:3,1:3,c,i,e))
|
crystallite_invFi(1:3,1:3,c,i,e))
|
||||||
crystallite_subdt(c,i,e) = crystallite_subStep(c,i,e) * crystallite_dt(c,i,e)
|
crystallite_subdt(c,i,e) = crystallite_subStep(c,i,e) * crystallite_dt(c,i,e)
|
||||||
crystallite_converged(c,i,e) = .false.
|
crystallite_converged(c,i,e) = .false.
|
||||||
endif
|
endif
|
||||||
|
|
|
@ -0,0 +1,46 @@
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!> @brief New fortran functions for compiler versions that do not support them
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
module future
|
||||||
|
public
|
||||||
|
contains
|
||||||
|
|
||||||
|
#if defined(__GFORTRAN__) || __INTEL_COMPILER < 1800
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief substitute for the findloc intrinsic (only for integer, dimension(:) at the moment)
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
function findloc(a,v)
|
||||||
|
integer, intent(in), dimension(:) :: a
|
||||||
|
integer, intent(in) :: v
|
||||||
|
integer :: i,j
|
||||||
|
integer, allocatable, dimension(:) :: findloc
|
||||||
|
|
||||||
|
allocate(findloc(count(a==v)))
|
||||||
|
j = 1
|
||||||
|
do i = 1, size(a)
|
||||||
|
if (a(i)==v) then
|
||||||
|
findloc(j) = i
|
||||||
|
j = j + 1
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
end function findloc
|
||||||
|
#endif
|
||||||
|
|
||||||
|
#if defined(__PGI)
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief substitute for the norm2 intrinsic (only for real,dimension(3) at the moment)
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
real(pReal) pure function norm2(v)
|
||||||
|
use prec, only: &
|
||||||
|
pReal
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
real(pReal), intent(in), dimension(3) :: v
|
||||||
|
|
||||||
|
norm2 = sqrt(sum(v**2))
|
||||||
|
|
||||||
|
end function norm2
|
||||||
|
#endif
|
||||||
|
|
||||||
|
end module future
|
|
@ -9,6 +9,7 @@
|
||||||
module lattice
|
module lattice
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pReal
|
pReal
|
||||||
|
use future
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
|
@ -8,6 +8,7 @@
|
||||||
module math
|
module math
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pReal
|
pReal
|
||||||
|
use future
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
|
@ -8,13 +8,14 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module mesh_base
|
module mesh_base
|
||||||
|
|
||||||
use, intrinsic :: iso_c_binding
|
use, intrinsic :: iso_c_binding
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pStringLen, &
|
pStringLen, &
|
||||||
pReal, &
|
pReal, &
|
||||||
pInt
|
pInt
|
||||||
use element, only: &
|
use element, only: &
|
||||||
tElement
|
tElement
|
||||||
|
use future
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,8 @@
|
||||||
module plastic_nonlocal
|
module plastic_nonlocal
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pReal
|
pReal
|
||||||
|
use future
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
real(pReal), parameter, private :: &
|
real(pReal), parameter, private :: &
|
||||||
|
|
|
@ -36,6 +36,7 @@
|
||||||
module quaternions
|
module quaternions
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pReal
|
pReal
|
||||||
|
use future
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
public
|
public
|
||||||
|
|
Loading…
Reference in New Issue