2012-07-30 19:36:22 +05:30
!--------------------------------------------------------------------------------------------------
2012-08-03 14:55:48 +05:30
! $Id$
2012-07-30 19:36:22 +05:30
!--------------------------------------------------------------------------------------------------
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Basic scheme solver
2012-08-29 00:49:47 +05:30
!> @details this solver follows closely the original large strain formulation presented by
!> Suquet. The iterative procedure is solved using a fix-point iteration
2012-07-30 19:36:22 +05:30
!--------------------------------------------------------------------------------------------------
2012-07-24 22:37:10 +05:30
module DAMASK_spectral_SolverBasic
2012-08-03 14:55:48 +05:30
use prec , only : &
pInt , &
pReal
2012-07-25 19:31:39 +05:30
2012-07-30 19:36:22 +05:30
use math , only : &
2012-08-03 14:55:48 +05:30
math_I3
2012-07-25 19:31:39 +05:30
2012-08-03 14:55:48 +05:30
use DAMASK_spectral_Utilities , only : &
2012-10-02 20:56:56 +05:30
tSolutionState
2012-07-25 19:31:39 +05:30
2012-08-03 14:55:48 +05:30
implicit none
2012-07-25 19:31:39 +05:30
character ( len = * ) , parameter , public :: &
DAMASK_spectral_SolverBasic_label = 'basic'
!--------------------------------------------------------------------------------------------------
2012-08-03 14:55:48 +05:30
! pointwise data
2012-10-02 20:56:56 +05:30
real ( pReal ) , private , dimension ( : , : , : , : , : ) , allocatable :: F , F_lastInc , Fdot , P
2012-08-03 14:55:48 +05:30
real ( pReal ) , private , dimension ( : , : , : , : ) , allocatable :: coordinates
real ( pReal ) , private , dimension ( : , : , : ) , allocatable :: temperature
2012-07-25 19:31:39 +05:30
!--------------------------------------------------------------------------------------------------
! stress, stiffness and compliance average etc.
2012-08-03 14:55:48 +05:30
real ( pReal ) , private , dimension ( 3 , 3 ) :: &
2012-07-25 19:31:39 +05:30
F_aim = math_I3 , &
2012-10-24 17:01:40 +05:30
F_aim_lastInc = math_I3 , &
F_aimDot = 0.0_pReal
2012-08-03 14:55:48 +05:30
real ( pReal ) , private , dimension ( 3 , 3 , 3 , 3 ) :: &
2012-10-02 20:56:56 +05:30
C = 0.0_pReal , C_lastInc = 0.0_pReal
2012-07-25 19:31:39 +05:30
2012-08-29 00:49:47 +05:30
contains
2012-07-24 22:37:10 +05:30
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief allocates all neccessary fields and fills them with data, potentially from restart info
!--------------------------------------------------------------------------------------------------
subroutine basic_init ( )
2012-08-27 13:34:47 +05:30
use , intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
2012-08-03 14:55:48 +05:30
use IO , only : &
IO_read_JobBinaryFile , &
2012-08-31 01:56:28 +05:30
IO_write_JobBinaryFile , &
IO_intOut
2012-07-25 19:31:39 +05:30
2012-08-03 14:55:48 +05:30
use FEsolving , only : &
restartInc
2012-07-25 19:31:39 +05:30
2012-08-03 14:55:48 +05:30
use DAMASK_interface , only : &
getSolverJobName
2012-07-25 19:31:39 +05:30
2012-08-03 14:55:48 +05:30
use DAMASK_spectral_Utilities , only : &
Utilities_init , &
Utilities_constitutiveResponse , &
Utilities_updateGamma , &
2012-10-02 20:56:56 +05:30
debugRestart
2012-08-03 14:55:48 +05:30
use mesh , only : &
res , &
geomdim
implicit none
integer ( pInt ) :: i , j , k
real ( pReal ) , dimension ( 3 , 3 ) :: temp33_Real
2012-10-24 17:01:40 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: temp3333_Real
2012-07-30 19:36:22 +05:30
2012-10-24 17:01:40 +05:30
2012-08-03 14:55:48 +05:30
call Utilities_Init ( )
2012-10-02 20:56:56 +05:30
write ( 6 , '(/,a)' ) ' <<<+- DAMASK_spectral_solverBasic init -+>>>'
2012-08-03 14:55:48 +05:30
write ( 6 , '(a)' ) ' $Id$'
2012-07-30 19:36:22 +05:30
#include "compilation_info.f90"
2012-08-03 14:55:48 +05:30
write ( 6 , '(a)' ) ''
2012-08-09 18:34:56 +05:30
allocate ( F ( 3 , 3 , res ( 1 ) , res ( 2 ) , res ( 3 ) ) , source = 0.0_pReal )
allocate ( F_lastInc ( 3 , 3 , res ( 1 ) , res ( 2 ) , res ( 3 ) ) , source = 0.0_pReal )
2012-10-02 20:56:56 +05:30
allocate ( Fdot ( 3 , 3 , res ( 1 ) , res ( 2 ) , res ( 3 ) ) , source = 0.0_pReal )
2012-08-09 18:34:56 +05:30
allocate ( P ( 3 , 3 , res ( 1 ) , res ( 2 ) , res ( 3 ) ) , source = 0.0_pReal )
2012-10-24 17:01:40 +05:30
allocate ( coordinates ( res ( 1 ) , res ( 2 ) , res ( 3 ) , 3 ) , source = 0.0_pReal )
allocate ( temperature ( res ( 1 ) , res ( 2 ) , res ( 3 ) ) , source = 0.0_pReal )
2012-07-25 19:31:39 +05:30
!--------------------------------------------------------------------------------------------------
! init fields
2012-08-03 14:55:48 +05:30
if ( restartInc == 1_pInt ) then ! no deformation (no restart)
2012-08-09 18:34:56 +05:30
F = spread ( spread ( spread ( math_I3 , 3 , res ( 1 ) ) , 4 , res ( 2 ) ) , 5 , res ( 3 ) ) ! initialize to identity
F_lastInc = F
2012-08-03 14:55:48 +05:30
do k = 1_pInt , res ( 3 ) ; do j = 1_pInt , res ( 2 ) ; do i = 1_pInt , res ( 1 )
coordinates ( i , j , k , 1 : 3 ) = geomdim / real ( res , pReal ) * real ( [ i , j , k ] , pReal ) &
- geomdim / real ( 2_pInt * res , pReal )
enddo ; enddo ; enddo
2012-10-24 17:01:40 +05:30
2012-08-03 14:55:48 +05:30
elseif ( restartInc > 1_pInt ) then ! using old values from file
2012-08-31 01:56:28 +05:30
if ( debugRestart ) write ( 6 , '(a,' / / IO_intOut ( restartInc - 1_pInt ) / / ',a)' ) &
'Reading values of increment' , restartInc - 1_pInt , 'from file'
2012-08-03 14:55:48 +05:30
call IO_read_jobBinaryFile ( 777 , 'convergedSpectralDefgrad' , &
2012-07-25 19:31:39 +05:30
trim ( getSolverJobName ( ) ) , size ( F ) )
2012-08-03 14:55:48 +05:30
read ( 777 , rec = 1 ) F
close ( 777 )
call IO_read_jobBinaryFile ( 777 , 'convergedSpectralDefgrad_lastInc' , &
2012-07-25 19:31:39 +05:30
trim ( getSolverJobName ( ) ) , size ( F_lastInc ) )
2012-08-03 14:55:48 +05:30
read ( 777 , rec = 1 ) F_lastInc
close ( 777 )
call IO_read_jobBinaryFile ( 777 , 'F_aim' , trim ( getSolverJobName ( ) ) , size ( F_aim ) )
read ( 777 , rec = 1 ) F_aim
close ( 777 )
call IO_read_jobBinaryFile ( 777 , 'F_aim_lastInc' , trim ( getSolverJobName ( ) ) , size ( F_aim_lastInc ) )
read ( 777 , rec = 1 ) F_aim_lastInc
close ( 777 )
2012-10-24 17:01:40 +05:30
call IO_read_jobBinaryFile ( 777 , 'C_lastInc' , trim ( getSolverJobName ( ) ) , size ( C_lastInc ) )
read ( 777 , rec = 1 ) C_lastInc
close ( 777 )
call IO_read_jobBinaryFile ( 777 , 'C' , trim ( getSolverJobName ( ) ) , size ( C ) )
read ( 777 , rec = 1 ) C
close ( 777 )
call IO_read_jobBinaryFile ( 777 , 'F_aimDot' , trim ( getSolverJobName ( ) ) , size ( f_aimDot ) )
read ( 777 , rec = 1 ) f_aimDot
close ( 777 )
call IO_read_jobBinaryFile ( 777 , 'C_ref' , trim ( getSolverJobName ( ) ) , size ( temp3333_Real ) )
read ( 777 , rec = 1 ) temp3333_Real
close ( 777 )
2012-08-03 14:55:48 +05:30
coordinates = 0.0 ! change it later!!!
endif
2012-10-24 17:01:40 +05:30
call Utilities_constitutiveResponse ( coordinates , F , F , temperature , 0.0_pReal , &
2012-08-03 14:55:48 +05:30
P , C , temp33_Real , . false . , math_I3 )
2012-10-24 17:01:40 +05:30
!no rotation bc call deformed_fft(res,geomdim,math_rotate_backward33(F_aim,rotation_BC),1.0_pReal,F_lastInc,coordinates)
2012-07-25 19:31:39 +05:30
!--------------------------------------------------------------------------------------------------
! reference stiffness
2012-10-24 17:01:40 +05:30
if ( restartInc == 1_pInt ) then ! use initial stiffness as reference stiffness
temp3333_Real = C
endif
2012-07-25 19:31:39 +05:30
2012-10-24 17:01:40 +05:30
call Utilities_updateGamma ( temp3333_Real , . True . )
2012-07-24 22:37:10 +05:30
2012-08-03 14:55:48 +05:30
end subroutine basic_init
!--------------------------------------------------------------------------------------------------
!> @brief solution for the basic scheme with internal iterations
!--------------------------------------------------------------------------------------------------
2012-10-02 20:56:56 +05:30
type ( tSolutionState ) function &
basic_solution ( incInfo , guessmode , timeinc , timeinc_old , P_BC , F_BC , temperature_bc , rotation_BC )
2012-07-24 22:37:10 +05:30
use numerics , only : &
2012-07-26 19:28:47 +05:30
itmax , &
itmin , &
update_gamma
2012-08-03 14:55:48 +05:30
use math , only : &
math_mul33x33 , &
math_rotate_backward33 , &
math_transpose33 , &
2012-08-27 13:34:47 +05:30
math_mul3333xx33
2012-08-03 14:55:48 +05:30
use mesh , only : &
res , &
2012-08-27 13:34:47 +05:30
geomdim , &
2012-10-02 20:56:56 +05:30
deformed_fft , &
wgt
2012-07-24 22:37:10 +05:30
use IO , only : &
2012-08-31 01:56:28 +05:30
IO_write_JobBinaryFile , &
IO_intOut
2012-08-03 14:55:48 +05:30
use DAMASK_spectral_Utilities , only : &
2012-10-02 20:56:56 +05:30
tBoundaryCondition , &
2012-08-03 14:55:48 +05:30
field_real , &
Utilities_forwardField , &
Utilities_maskedCompliance , &
2012-10-02 20:56:56 +05:30
Utilities_FFTforward , &
2012-08-03 14:55:48 +05:30
Utilities_divergenceRMS , &
Utilities_fourierConvolution , &
2012-10-02 20:56:56 +05:30
Utilities_FFTbackward , &
2012-08-03 14:55:48 +05:30
Utilities_updateGamma , &
2012-10-02 20:56:56 +05:30
Utilities_constitutiveResponse , &
Utilities_calculateRate
2012-08-03 14:55:48 +05:30
2012-07-24 22:37:10 +05:30
use FEsolving , only : &
2012-08-29 11:20:42 +05:30
restartWrite , &
2012-10-24 17:01:40 +05:30
restartRead , &
2012-08-29 11:20:42 +05:30
terminallyIll
2012-10-24 17:01:40 +05:30
use DAMASK_spectral_Utilities , only : &
cutBack
2012-07-24 22:37:10 +05:30
implicit none
!--------------------------------------------------------------------------------------------------
! input data for solution
2012-08-03 14:55:48 +05:30
real ( pReal ) , intent ( in ) :: timeinc , timeinc_old , temperature_bc , guessmode
2012-10-02 20:56:56 +05:30
type ( tBoundaryCondition ) , intent ( in ) :: P_BC , F_BC
character ( len = * ) , intent ( in ) :: incInfo
2012-08-03 14:55:48 +05:30
real ( pReal ) , dimension ( 3 , 3 ) , intent ( in ) :: rotation_BC
2012-07-24 22:37:10 +05:30
2012-07-25 19:31:39 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: S
2012-10-24 17:01:40 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: F_aim_lab , &
2012-07-26 19:28:47 +05:30
F_aim_lab_lastIter , &
P_av
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
! loop variables, convergence etc.
2012-07-25 19:31:39 +05:30
real ( pReal ) :: err_div , err_stress
2012-08-03 14:55:48 +05:30
integer ( pInt ) :: iter , row , column , i , j , k
2012-07-25 19:31:39 +05:30
logical :: ForwardData
2012-08-03 14:55:48 +05:30
real ( pReal ) :: defgradDet , defgradDetMax , defgradDetMin
real ( pReal ) , dimension ( 3 , 3 ) :: temp33_Real
2012-07-24 22:37:10 +05:30
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
! restart information for spectral solver
2012-07-24 22:37:10 +05:30
if ( restartWrite ) then
write ( 6 , '(a)' ) 'writing converged results for restart'
2012-10-24 17:01:40 +05:30
call IO_write_jobBinaryFile ( 777 , 'convergedSpectralDefgrad' , size ( F ) ) ! writing deformation gradient field to file
write ( 777 , rec = 1 ) F
close ( 777 )
call IO_write_jobBinaryFile ( 777 , 'convergedSpectralDefgrad_lastInc' , size ( F_lastInc ) ) ! writing F_lastInc field to file
write ( 777 , rec = 1 ) F_lastInc
2012-07-24 22:37:10 +05:30
close ( 777 )
2012-10-24 17:01:40 +05:30
call IO_write_jobBinaryFile ( 777 , 'F_aim' , size ( F_aim ) )
write ( 777 , rec = 1 ) F_aim
close ( 777 )
call IO_write_jobBinaryFile ( 777 , 'F_aim_lastInc' , size ( F_aim_lastInc ) )
write ( 777 , rec = 1 ) F_aim_lastInc
close ( 777 )
2012-07-24 22:37:10 +05:30
call IO_write_jobBinaryFile ( 777 , 'C' , size ( C ) )
write ( 777 , rec = 1 ) C
close ( 777 )
2012-10-24 17:01:40 +05:30
call IO_write_jobBinaryFile ( 777 , 'C_lastInc' , size ( C_lastInc ) )
write ( 777 , rec = 1 ) C_lastInc
close ( 777 )
call IO_write_jobBinaryFile ( 777 , 'F_aimDot' , size ( f_aimDot ) )
write ( 777 , rec = 1 ) f_aimDot
close ( 777 )
2012-07-24 22:37:10 +05:30
endif
2012-10-02 20:56:56 +05:30
if ( cutBack ) then
2012-10-24 17:01:40 +05:30
F_aim = F_aim_lastInc
F = F_lastInc
C = C_lastInc
else
C_lastInc = C
2012-07-24 22:37:10 +05:30
!--------------------------------------------------------------------------------------------------
2012-10-02 20:56:56 +05:30
! calculate rate for aim
if ( F_BC % myType == 'l' ) then ! calculate f_aimDot from given L and current F
f_aimDot = F_BC % maskFloat * math_mul33x33 ( F_BC % values , F_aim )
elseif ( F_BC % myType == 'fdot' ) then ! f_aimDot is prescribed
f_aimDot = F_BC % maskFloat * F_BC % values
endif
f_aimDot = f_aimDot &
+ guessmode * P_BC % maskFloat * ( F_aim - F_aim_lastInc ) / timeinc_old
F_aim_lastInc = F_aim
2012-10-24 17:01:40 +05:30
print * , 'F_aimDot' , f_aimDot
print * , 'guessmode' , guessmode
2012-10-02 20:56:56 +05:30
!--------------------------------------------------------------------------------------------------
! update coordinates and rate and forward last inc
call deformed_fft ( res , geomdim , math_rotate_backward33 ( F_aim_lastInc , rotation_BC ) , &
1.0_pReal , F_lastInc , coordinates )
Fdot = Utilities_calculateRate ( math_rotate_backward33 ( f_aimDot , rotation_BC ) , &
timeinc , timeinc_old , guessmode , F_lastInc , F )
F_lastInc = F
endif
F_aim = F_aim + f_aimDot * timeinc
2012-10-24 17:01:40 +05:30
F = Utilities_forwardField ( timeinc , F_aim , F_lastInc , Fdot ) !I think F aim should be rotated here
2012-10-19 14:14:21 +05:30
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
! update stiffness (and gamma operator)
S = Utilities_maskedCompliance ( rotation_BC , P_BC % maskLogical , C )
2012-10-19 14:14:21 +05:30
2012-10-24 17:01:40 +05:30
if ( update_gamma ) call Utilities_updateGamma ( C , restartWrite )
2012-08-03 14:55:48 +05:30
2012-10-24 17:01:40 +05:30
if ( . not . restartRead ) ForwardData = . True .
2012-08-03 14:55:48 +05:30
iter = 0_pInt
convergenceLoop : do while ( iter < itmax )
2012-07-24 22:37:10 +05:30
iter = iter + 1_pInt
!--------------------------------------------------------------------------------------------------
! report begin of new iteration
2012-10-02 20:56:56 +05:30
write ( 6 , '(/,a,3(a,' / / IO_intOut ( itmax ) / / '))' ) trim ( incInfo ) , &
2012-10-19 14:14:21 +05:30
' @ Iter. ' , itmin , '≤' , iter , '≤' , itmax
2012-08-03 14:55:48 +05:30
write ( 6 , '(a,/,3(3(f12.7,1x)/))' , advance = 'no' ) 'deformation gradient aim =' , &
math_transpose33 ( F_aim )
2012-07-24 22:37:10 +05:30
F_aim_lab_lastIter = math_rotate_backward33 ( F_aim , rotation_BC )
!--------------------------------------------------------------------------------------------------
! evaluate constitutive response
2012-10-02 20:56:56 +05:30
basic_solution % termIll = . false .
2012-07-30 19:36:22 +05:30
call Utilities_constitutiveResponse ( coordinates , F_lastInc , F , temperature , timeinc , &
2012-08-03 14:55:48 +05:30
P , C , P_av , ForwardData , rotation_BC )
2012-08-29 11:20:42 +05:30
basic_solution % termIll = terminallyIll
2012-10-02 20:56:56 +05:30
terminallyIll = . False .
2012-07-25 19:31:39 +05:30
ForwardData = . False .
2012-07-24 22:37:10 +05:30
!--------------------------------------------------------------------------------------------------
! stress BC handling
2012-10-02 20:56:56 +05:30
F_aim = F_aim - math_mul3333xx33 ( S , ( ( P_av - P_BC % values ) ) ) ! S = 0.0 for no bc
err_stress = maxval ( abs ( P_BC % maskFloat * ( P_av - P_BC % values ) ) ) ! mask = 0.0 for no bc
F_aim_lab = math_rotate_backward33 ( F_aim , rotation_BC ) ! boundary conditions from load frame into lab (Fourier) frame
2012-07-24 22:37:10 +05:30
!--------------------------------------------------------------------------------------------------
2012-08-03 14:55:48 +05:30
! updated deformation gradient using fix point algorithm of basic scheme
field_real = 0.0_pReal
2012-08-09 18:34:56 +05:30
field_real ( 1 : res ( 1 ) , 1 : res ( 2 ) , 1 : res ( 3 ) , 1 : 3 , 1 : 3 ) = reshape ( P , [ res ( 1 ) , res ( 2 ) , res ( 3 ) , 3 , 3 ] , &
order = [ 4 , 5 , 1 , 2 , 3 ] ) ! field real has a different order
2012-10-02 20:56:56 +05:30
call Utilities_FFTforward ( )
2012-08-03 14:55:48 +05:30
err_div = Utilities_divergenceRMS ( )
call Utilities_fourierConvolution ( F_aim_lab_lastIter - F_aim_lab )
2012-10-02 20:56:56 +05:30
call Utilities_FFTbackward ( )
2012-08-09 18:34:56 +05:30
F = F - reshape ( field_real ( 1 : res ( 1 ) , 1 : res ( 2 ) , 1 : res ( 3 ) , 1 : 3 , 1 : 3 ) , shape ( F ) , order = [ 3 , 4 , 5 , 1 , 2 ] ) ! F(x)^(n+1) = F(x)^(n) + correction; *wgt: correcting for missing normalization
2012-08-06 14:23:12 +05:30
basic_solution % converged = basic_Converged ( err_div , P_av , err_stress , P_av )
2012-10-02 20:56:56 +05:30
write ( 6 , '(/,a)' ) '=========================================================================='
2012-10-19 14:14:21 +05:30
if ( ( basic_solution % converged . and . iter > = itmin ) . or . basic_solution % termIll ) then
basic_solution % iterationsNeeded = iter
exit
endif
2012-07-24 22:37:10 +05:30
enddo convergenceLoop
end function basic_solution
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief convergence check for basic scheme based on div of P and deviation from stress aim
!--------------------------------------------------------------------------------------------------
2012-08-06 14:23:12 +05:30
logical function basic_Converged ( err_div , pAvgDiv , err_stress , pAvgStress )
2012-07-30 19:36:22 +05:30
use numerics , only : &
2012-08-03 14:55:48 +05:30
itmin , &
err_div_tol , &
err_stress_tolrel , &
err_stress_tolabs
use math , only : &
math_mul33x33 , &
math_eigenvalues33 , &
math_transpose33
2012-07-26 19:28:47 +05:30
2012-07-30 19:36:22 +05:30
implicit none
2012-08-03 14:55:48 +05:30
real ( pReal ) , dimension ( 3 , 3 ) , intent ( in ) :: &
pAvgDiv , &
pAvgStress
real ( pReal ) , intent ( in ) :: &
err_div , &
err_stress
real ( pReal ) :: &
err_stress_tol , &
pAvgDivL2
2012-07-26 19:28:47 +05:30
2012-08-03 14:55:48 +05:30
pAvgDivL2 = sqrt ( maxval ( math_eigenvalues33 ( math_mul33x33 ( pAvgDiv , math_transpose33 ( pAvgDiv ) ) ) ) ) ! L_2 norm of average stress (http://mathworld.wolfram.com/SpectralNorm.html)
err_stress_tol = min ( maxval ( abs ( pAvgStress ) ) * err_stress_tolrel , err_stress_tolabs )
2012-08-06 14:23:12 +05:30
basic_Converged = all ( [ err_div / pAvgDivL2 / err_div_tol , &
2012-08-03 14:55:48 +05:30
err_stress / err_stress_tol ] < 1.0_pReal )
2012-07-26 19:28:47 +05:30
2012-08-03 14:55:48 +05:30
write ( 6 , '(a,f6.2,a,es11.4,a)' ) 'error divergence = ' , err_div / pAvgDivL2 / err_div_tol , &
' (' , err_div , ' N/m³)'
write ( 6 , '(a,f6.2,a,es11.4,a)' ) 'error stress = ' , err_stress / err_stress_tol , &
' (' , err_stress , ' Pa)'
2012-07-26 19:28:47 +05:30
2012-08-06 14:23:12 +05:30
end function basic_Converged
2012-07-25 19:31:39 +05:30
2012-10-02 20:56:56 +05:30
2012-08-03 14:55:48 +05:30
subroutine basic_destroy ( )
use DAMASK_spectral_Utilities , only : &
Utilities_destroy
implicit none
call Utilities_destroy ( )
2012-07-25 19:31:39 +05:30
end subroutine basic_destroy
2012-10-02 20:56:56 +05:30
2012-07-25 19:31:39 +05:30
end module DAMASK_spectral_SolverBasic
2012-07-30 19:36:22 +05:30
!--------------------------------------------------------------------------------------------------
! calculate some additional output
! if(debugGeneral) then
! maxCorrectionSkew = 0.0_pReal
! maxCorrectionSym = 0.0_pReal
! temp33_Real = 0.0_pReal
! do k = 1_pInt, res(3); do j = 1_pInt, res(2); do i = 1_pInt, res(1)
! maxCorrectionSym = max(maxCorrectionSym,&
! maxval(math_symmetric33(field_real(i,j,k,1:3,1:3))))
! maxCorrectionSkew = max(maxCorrectionSkew,&
! maxval(math_skew33(field_real(i,j,k,1:3,1:3))))
! temp33_Real = temp33_Real + field_real(i,j,k,1:3,1:3)
! enddo; enddo; enddo
! write(6,'(a,1x,es11.4)') 'max symmetric correction of deformation =',&
! maxCorrectionSym*wgt
! write(6,'(a,1x,es11.4)') 'max skew correction of deformation =',&
! maxCorrectionSkew*wgt
! write(6,'(a,1x,es11.4)') 'max sym/skew of avg correction = ',&
! maxval(math_symmetric33(temp33_real))/&
! maxval(math_skew33(temp33_real))
! endif
!--------------------------------------------------------------------------------------------------
! calculate bounds of det(F) and report
! if(debugGeneral) then
! defgradDetMax = -huge(1.0_pReal)
! defgradDetMin = +huge(1.0_pReal)
! do k = 1_pInt, res(3); do j = 1_pInt, res(2); do i = 1_pInt, res(1)
! defgradDet = math_det33(F(i,j,k,1:3,1:3))
! defgradDetMax = max(defgradDetMax,defgradDet)
! defgradDetMin = min(defgradDetMin,defgradDet)
! enddo; enddo; enddo
! write(6,'(a,1x,es11.4)') 'max determinant of deformation =', defgradDetMax
! write(6,'(a,1x,es11.4)') 'min determinant of deformation =', defgradDetMin
! endif