some comments and minor improvements.
removed tol_gravityNodePos from prec because it's not used tol_math_check is now used by spectral driver to check rotation
This commit is contained in:
parent
3eb8aa1362
commit
3bf0ed84c8
|
@ -31,7 +31,8 @@ program DAMASK_spectral_Driver
|
|||
iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
|
||||
use prec, only: &
|
||||
pInt, &
|
||||
pReal
|
||||
pReal, &
|
||||
tol_math_check
|
||||
use DAMASK_interface, only: &
|
||||
DAMASK_interface_init, &
|
||||
loadCaseFile, &
|
||||
|
@ -66,7 +67,6 @@ program DAMASK_spectral_Driver
|
|||
restartInc
|
||||
use numerics, only: &
|
||||
maxCutBack, &
|
||||
rotation_tol, &
|
||||
mySpectralSolver, &
|
||||
regridMode
|
||||
use homogenization, only: &
|
||||
|
@ -310,9 +310,9 @@ program DAMASK_spectral_Driver
|
|||
transpose(loadCases(currentLoadCase)%P%maskLogical))
|
||||
if (any(abs(math_mul33x33(loadCases(currentLoadCase)%rotation, &
|
||||
math_transpose33(loadCases(currentLoadCase)%rotation))-math_I3) >&
|
||||
reshape(spread(rotation_tol,1,9),[ 3,3]))&
|
||||
reshape(spread(tol_math_check,1,9),[ 3,3]))&
|
||||
.or. abs(math_det33(loadCases(currentLoadCase)%rotation)) > &
|
||||
1.0_pReal + rotation_tol) errorID = 846_pInt ! given rotation matrix contains strain
|
||||
1.0_pReal + tol_math_check) errorID = 846_pInt ! given rotation matrix contains strain
|
||||
if (any(loadCases(currentLoadCase)%rotation /= math_I3)) &
|
||||
write(6,'(2x,a,/,3(3(3x,f12.7,1x)/))',advance='no') 'rotation of loadframe:',&
|
||||
math_transpose33(loadCases(currentLoadCase)%rotation)
|
||||
|
|
|
@ -71,7 +71,6 @@ subroutine DAMASK_interface_init(loadCaseParameterIn,geometryParameterIn)
|
|||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||
|
||||
implicit none
|
||||
|
||||
character(len=1024), optional, intent(in) :: &
|
||||
loadCaseParameterIn, & !< if using the f2py variant, the -l argument of DAMASK_spectral.exe
|
||||
geometryParameterIn !< if using the f2py variant, the -g argument of DAMASK_spectral.exe
|
||||
|
@ -86,7 +85,7 @@ subroutine DAMASK_interface_init(loadCaseParameterIn,geometryParameterIn)
|
|||
integer :: &
|
||||
i
|
||||
integer, parameter :: &
|
||||
maxNchunks = 128 !< DAMASK_spectral + (l,g,w,r)*2 + h
|
||||
maxNchunks = 128 !< DAMASK_spectral + (l,g,w,r)*2 + h
|
||||
integer, dimension(1+ 2* maxNchunks) :: &
|
||||
positions
|
||||
integer, dimension(8) :: &
|
||||
|
@ -118,7 +117,7 @@ subroutine DAMASK_interface_init(loadCaseParameterIn,geometryParameterIn)
|
|||
call get_command(commandLine)
|
||||
positions = IIO_stringPos(commandLine,maxNchunks)
|
||||
do i = 1, positions(1)
|
||||
tag = IIO_lc(IIO_stringValue(commandLine,positions,i)) ! extract key
|
||||
tag = IIO_lc(IIO_stringValue(commandLine,positions,i)) ! extract key
|
||||
select case(tag)
|
||||
case ('-h','--help')
|
||||
write(6,'(a)') ' #######################################################################'
|
||||
|
@ -230,14 +229,15 @@ end subroutine DAMASK_interface_init
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief extract working directory from loadcase file possibly based on current working dir
|
||||
!> @todo change working directory with call chdir(storeWorkingDirectory)?
|
||||
!> @brief extract working directory from given argument or from location of geometry file,
|
||||
!! possibly converting relative arguments to absolut path
|
||||
!> @todo change working directory with call chdir(storeWorkingDirectory)?
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
character(len=1024) function storeWorkingDirectory(workingDirectoryArg,geometryArg)
|
||||
|
||||
implicit none
|
||||
character(len=*), intent(in) :: workingDirectoryArg
|
||||
character(len=*), intent(in) :: geometryArg
|
||||
character(len=*), intent(in) :: workingDirectoryArg !< working directory argument
|
||||
character(len=*), intent(in) :: geometryArg !< geometry argument
|
||||
character(len=1024) :: cwd
|
||||
character :: pathSep
|
||||
logical :: dirExists
|
||||
|
@ -278,7 +278,6 @@ end function storeWorkingDirectory
|
|||
character(len=1024) function getSolverWorkingDirectoryName()
|
||||
|
||||
implicit none
|
||||
|
||||
getSolverWorkingDirectoryName = workingDirectory
|
||||
|
||||
end function getSolverWorkingDirectoryName
|
||||
|
@ -448,8 +447,11 @@ end function makeRelativePath
|
|||
character function getPathSep()
|
||||
|
||||
implicit none
|
||||
character(len=2048) path
|
||||
integer(pInt) :: backslash = 0_pInt, slash = 0_pInt
|
||||
character(len=2048) :: &
|
||||
path
|
||||
integer(pInt) :: &
|
||||
backslash = 0_pInt, &
|
||||
slash = 0_pInt
|
||||
integer :: i
|
||||
|
||||
call get_environment_variable('PATH',path)
|
||||
|
|
|
@ -33,8 +33,9 @@ SHELL = /bin/sh
|
|||
# IMKLROOT = pathinfo:IMKL (will be adjusted by setup_code.py if present in pathinfo)
|
||||
# ACMLROOT = pathinfo:ACML (will be adjusted by setup_code.py if present in pathinfo)
|
||||
# LAPACKROOT = pathinfo:LAPACK (will be adjusted by setup_code.py if present in pathinfo)
|
||||
# PREFIX = arbitrary prefix
|
||||
# SUFFIX = arbitrary suffix
|
||||
# PREFIX = arbitrary prefix (before compilername)
|
||||
# OPTION = arbitrary option (just before file to compile)
|
||||
# SUFFIX = arbitrary suffix (after file to compile)
|
||||
# STANDARD_CHECK = checking for Fortran 2008, compiler dependend
|
||||
########################################################################################
|
||||
|
||||
|
@ -327,9 +328,9 @@ DEBUG_OPTIONS_gfortran :=-g\
|
|||
# underflow
|
||||
|
||||
ifeq "$(DEBUG)" "ON"
|
||||
COMPILE_OPTIONS_$(F90) :=$(COMPILE_OPTIONS_$(F90)) $(DEBUG_OPTIONS_$(F90))
|
||||
COMPILE_OPTIONS_$(F90) +=$(DEBUG_OPTIONS_$(F90))
|
||||
endif
|
||||
|
||||
COMPILE_OPTIONS_$(F90) +=$(OPTIONS)
|
||||
PRECISION_ifort :=-real-size 64 -integer-size 32 -DFLOAT=8 -DINT=4
|
||||
#-real-size 32: set precision to one of those 32/64/128 (= 4/8/16 bytes) for standard real (=8 for pReal)
|
||||
#-integer-size 16: set precision to one of those 16/32/64 (= 2/4/8 bytes) for standard integer (=4 for pInt)
|
||||
|
|
|
@ -302,7 +302,7 @@ subroutine constitutive_j2_init(myFile)
|
|||
constitutive_j2_Cslip_66(1:6,1:6,i) = lattice_symmetrizeC66(constitutive_j2_structureName(i),&
|
||||
constitutive_j2_Cslip_66(1:6,1:6,i))
|
||||
constitutive_j2_Cslip_66(1:6,1:6,i) = &
|
||||
math_Mandel3333to66(math_Voigt66to3333(constitutive_j2_Cslip_66(1:6,1:6,i))) ! todo what is going on here?
|
||||
math_Mandel3333to66(math_Voigt66to3333(constitutive_j2_Cslip_66(1:6,1:6,i))) ! Literature data is Voigt, DAMASK uses Mandel
|
||||
|
||||
enddo instancesLoop
|
||||
|
||||
|
|
|
@ -1374,7 +1374,6 @@ subroutine crystallite_integrateStateRK4()
|
|||
constitutive_microstructure
|
||||
|
||||
implicit none
|
||||
|
||||
real(pReal), dimension(4), parameter :: TIMESTEPFRACTION = [0.5_pReal, 0.5_pReal, 1.0_pReal, 1.0_pReal] ! factor giving the fraction of the original timestep used for Runge Kutta Integration
|
||||
real(pReal), dimension(4), parameter :: WEIGHT = [1.0_pReal, 2.0_pReal, 2.0_pReal, 1.0_pReal] ! weight of slope used for Runge Kutta integration
|
||||
|
||||
|
|
|
@ -19,11 +19,13 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
! $Id$
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @author Christoph Kords, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief setting precision for real and int type depending on makros "FLOAT" and "INT"
|
||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @author Christoph Kords, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief setting precision for real and int type depending on makros "FLOAT" and "INT"
|
||||
!> @details setting precision for real and int type and for DAMASK_NaN. Definition is made
|
||||
!! depending on makros "FLOAT" and "INT" defined during compilation
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
||||
module prec
|
||||
|
@ -62,10 +64,9 @@ module prec
|
|||
#endif
|
||||
|
||||
integer, parameter, public :: pLongInt = 8 !< integer representation 64 bit (was selected_int_kind(12), number with at least up to +- 1e12)
|
||||
real(pReal), parameter, public :: tol_math_check = 1.0e-8_pReal
|
||||
real(pReal), parameter, public :: tol_gravityNodePos = 1.0e-100_pReal
|
||||
real(pReal), parameter, public :: tol_math_check = 1.0e-8_pReal !< tolerance for internal math self-checks (rotation)
|
||||
|
||||
type, public :: p_vec
|
||||
type, public :: p_vec !< variable length datatype used for storage of state
|
||||
real(pReal), dimension(:), pointer :: p
|
||||
end type p_vec
|
||||
|
||||
|
|
Loading…
Reference in New Issue