2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief Managing of parameters related to numerics
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-07 15:37:29 +05:30
|
|
|
module numerics
|
2019-05-15 02:42:32 +05:30
|
|
|
use prec
|
2019-06-11 19:46:10 +05:30
|
|
|
use IO
|
|
|
|
|
|
|
|
#ifdef PETSc
|
|
|
|
#include <petsc/finclude/petscsys.h>
|
|
|
|
use petscsys
|
|
|
|
#endif
|
|
|
|
!$ use OMP_LIB
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2013-01-10 03:49:32 +05:30
|
|
|
implicit none
|
|
|
|
private
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2019-06-11 18:09:51 +05:30
|
|
|
integer, protected, public :: &
|
|
|
|
iJacoStiffness = 1, & !< frequency of stiffness update
|
|
|
|
nMPstate = 10, & !< materialpoint state loop limit
|
|
|
|
randomSeed = 0, & !< fixed seeding for pseudo-random number generator, Default 0: use random seed
|
|
|
|
worldrank = 0, & !< MPI worldrank (/=0 for MPI simulations only)
|
|
|
|
worldsize = 1, & !< MPI worldsize (/=1 for MPI simulations only)
|
|
|
|
numerics_integrator = 1 !< method used for state integration Default 1: fix-point iteration
|
2016-12-23 18:50:29 +05:30
|
|
|
integer(4), protected, public :: &
|
2013-09-26 22:51:46 +05:30
|
|
|
DAMASK_NumThreadsInt = 0 !< value stored in environment variable DAMASK_NUM_THREADS, set to zero if no OpenMP directive
|
2013-01-10 03:49:32 +05:30
|
|
|
real(pReal), protected, public :: &
|
2013-03-28 15:32:11 +05:30
|
|
|
defgradTolerance = 1.0e-7_pReal, & !< deviation of deformation gradient that is still allowed (used by CPFEM to determine outdated ffn1)
|
|
|
|
subStepMinHomog = 1.0e-3_pReal, & !< minimum (relative) size of sub-step allowed during cutback in homogenization
|
|
|
|
subStepSizeHomog = 0.25_pReal, & !< size of first substep when cutback in homogenization
|
|
|
|
stepIncreaseHomog = 1.5_pReal, & !< increase of next substep size when previous substep converged in homogenization
|
|
|
|
numerics_unitlength = 1.0_pReal, & !< determines the physical length of one computational length unit
|
|
|
|
absTol_RGC = 1.0e+4_pReal, & !< absolute tolerance of RGC residuum
|
|
|
|
relTol_RGC = 1.0e-3_pReal, & !< relative tolerance of RGC residuum
|
|
|
|
absMax_RGC = 1.0e+10_pReal, & !< absolute maximum of RGC residuum
|
|
|
|
relMax_RGC = 1.0e+2_pReal, & !< relative maximum of RGC residuum
|
|
|
|
pPert_RGC = 1.0e-7_pReal, & !< perturbation for computing RGC penalty tangent
|
|
|
|
xSmoo_RGC = 1.0e-5_pReal, & !< RGC penalty smoothing parameter (hyperbolic tangent)
|
|
|
|
viscPower_RGC = 1.0e+0_pReal, & !< power (sensitivity rate) of numerical viscosity in RGC scheme, Default 1.0e0: Newton viscosity (linear model)
|
|
|
|
viscModus_RGC = 0.0e+0_pReal, & !< stress modulus of RGC numerical viscosity, Default 0.0e0: No viscosity is applied
|
|
|
|
refRelaxRate_RGC = 1.0e-3_pReal, & !< reference relaxation rate in RGC viscosity
|
|
|
|
maxdRelax_RGC = 1.0e+0_pReal, & !< threshold of maximum relaxation vector increment (if exceed this then cutback)
|
|
|
|
maxVolDiscr_RGC = 1.0e-5_pReal, & !< threshold of maximum volume discrepancy allowed
|
|
|
|
volDiscrMod_RGC = 1.0e+12_pReal, & !< stiffness of RGC volume discrepancy (zero = without volume discrepancy constraint)
|
2014-06-25 04:48:07 +05:30
|
|
|
volDiscrPow_RGC = 5.0_pReal, & !< powerlaw penalty for volume discrepancy
|
2014-12-02 22:47:35 +05:30
|
|
|
charLength = 1.0_pReal, & !< characteristic length scale for gradient problems
|
|
|
|
residualStiffness = 1.0e-6_pReal !< non-zero residual damage
|
2013-03-28 15:32:11 +05:30
|
|
|
logical, protected, public :: &
|
2019-04-11 10:16:31 +05:30
|
|
|
usePingPong = .true.
|
2012-06-15 21:40:21 +05:30
|
|
|
|
2015-05-28 22:32:23 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! field parameters:
|
|
|
|
real(pReal), protected, public :: &
|
|
|
|
err_struct_tolAbs = 1.0e-10_pReal, & !< absolute tolerance for mechanical equilibrium
|
|
|
|
err_struct_tolRel = 1.0e-4_pReal, & !< relative tolerance for mechanical equilibrium
|
|
|
|
err_thermal_tolAbs = 1.0e-2_pReal, & !< absolute tolerance for thermal equilibrium
|
|
|
|
err_thermal_tolRel = 1.0e-6_pReal, & !< relative tolerance for thermal equilibrium
|
|
|
|
err_damage_tolAbs = 1.0e-2_pReal, & !< absolute tolerance for damage evolution
|
2019-03-07 11:39:00 +05:30
|
|
|
err_damage_tolRel = 1.0e-6_pReal !< relative tolerance for damage evolution
|
2019-06-11 18:09:51 +05:30
|
|
|
integer, protected, public :: &
|
|
|
|
itmax = 250, & !< maximum number of iterations
|
|
|
|
itmin = 1, & !< minimum number of iterations
|
|
|
|
stagItMax = 10, & !< max number of field level staggered iterations
|
|
|
|
maxCutBack = 3 !< max number of cut backs
|
2015-05-28 22:32:23 +05:30
|
|
|
|
2013-03-28 15:32:11 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! spectral parameters:
|
2019-03-23 13:57:58 +05:30
|
|
|
#ifdef Grid
|
2013-01-10 03:49:32 +05:30
|
|
|
real(pReal), protected, public :: &
|
2018-08-21 02:04:43 +05:30
|
|
|
err_div_tolAbs = 1.0e-4_pReal, & !< absolute tolerance for equilibrium
|
2013-08-07 22:50:05 +05:30
|
|
|
err_div_tolRel = 5.0e-4_pReal, & !< relative tolerance for equilibrium
|
|
|
|
err_curl_tolAbs = 1.0e-10_pReal, & !< absolute tolerance for compatibility
|
|
|
|
err_curl_tolRel = 5.0e-4_pReal, & !< relative tolerance for compatibility
|
|
|
|
err_stress_tolAbs = 1.0e3_pReal, & !< absolute tolerance for fullfillment of stress BC
|
|
|
|
err_stress_tolRel = 0.01_pReal, & !< relative tolerance for fullfillment of stress BC
|
2013-03-28 15:32:11 +05:30
|
|
|
rotation_tol = 1.0e-12_pReal, & !< tolerance of rotation specified in loadcase, Default 1.0e-12: first guess
|
|
|
|
polarAlpha = 1.0_pReal, & !< polarization scheme parameter 0.0 < alpha < 2.0. alpha = 1.0 ==> AL scheme, alpha = 2.0 ==> accelerated scheme
|
|
|
|
polarBeta = 1.0_pReal !< polarization scheme parameter 0.0 < beta < 2.0. beta = 1.0 ==> AL scheme, beta = 2.0 ==> accelerated scheme
|
2020-01-26 16:28:13 +05:30
|
|
|
character(len=pStringLen), protected, public :: &
|
2015-06-09 18:58:50 +05:30
|
|
|
petsc_options = ''
|
2012-10-02 20:56:56 +05:30
|
|
|
#endif
|
2011-02-07 20:05:42 +05:30
|
|
|
|
2014-06-06 06:08:29 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! FEM parameters:
|
|
|
|
#ifdef FEM
|
2019-06-11 18:09:51 +05:30
|
|
|
integer, protected, public :: &
|
|
|
|
integrationOrder = 2, & !< order of quadrature rule required
|
|
|
|
structOrder = 2 !< order of displacement shape functions
|
2015-05-28 22:32:23 +05:30
|
|
|
logical, protected, public :: &
|
|
|
|
BBarStabilisation = .false.
|
2020-01-26 17:48:29 +05:30
|
|
|
character(len=*), parameter, public :: &
|
2015-06-09 18:58:50 +05:30
|
|
|
petsc_defaultOptions = '-mech_snes_type newtonls &
|
2014-12-08 21:07:44 +05:30
|
|
|
&-mech_snes_linesearch_type cp &
|
|
|
|
&-mech_snes_ksp_ew &
|
|
|
|
&-mech_snes_ksp_ew_rtol0 0.01 &
|
|
|
|
&-mech_snes_ksp_ew_rtolmax 0.01 &
|
|
|
|
&-mech_ksp_type fgmres &
|
|
|
|
&-mech_ksp_max_it 25 &
|
|
|
|
&-mech_pc_type ml &
|
|
|
|
&-mech_mg_levels_ksp_type chebyshev &
|
|
|
|
&-mech_mg_levels_pc_type sor &
|
2020-01-26 17:48:29 +05:30
|
|
|
&-mech_pc_ml_nullspace user'
|
|
|
|
character(len=pStringLen), protected, public :: &
|
2015-06-09 18:58:50 +05:30
|
|
|
petsc_options = ''
|
2014-06-06 06:08:29 +05:30
|
|
|
#endif
|
|
|
|
|
2013-01-10 03:49:32 +05:30
|
|
|
public :: numerics_init
|
2012-10-02 20:56:56 +05:30
|
|
|
|
|
|
|
contains
|
2009-11-10 19:06:27 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief reads in parameters from numerics.config and sets openMP related parameters. Also does
|
|
|
|
! a sanity check
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-07 15:37:29 +05:30
|
|
|
subroutine numerics_init
|
|
|
|
!$ integer :: gotDAMASK_NUM_THREADS = 1
|
2019-06-11 18:09:51 +05:30
|
|
|
integer :: i,j, ierr
|
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-03-09 04:37:57 +05:30
|
|
|
character(len=pStringLen), dimension(:), allocatable :: fileContent
|
|
|
|
character(len=pStringLen) :: &
|
2013-07-31 20:33:38 +05:30
|
|
|
tag ,&
|
|
|
|
line
|
2019-03-09 04:37:57 +05:30
|
|
|
logical :: fexist
|
2012-06-12 15:14:05 +05:30
|
|
|
!$ character(len=6) DAMASK_NumThreadsString ! environment variable DAMASK_NUM_THREADS
|
2009-08-27 21:00:40 +05:30
|
|
|
|
2014-10-10 18:38:34 +05:30
|
|
|
#ifdef PETSc
|
2014-10-10 01:53:06 +05:30
|
|
|
call MPI_Comm_rank(PETSC_COMM_WORLD,worldrank,ierr);CHKERRQ(ierr)
|
|
|
|
call MPI_Comm_size(PETSC_COMM_WORLD,worldsize,ierr);CHKERRQ(ierr)
|
2014-10-10 18:38:34 +05:30
|
|
|
#endif
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- numerics init -+>>>'
|
2014-10-10 18:38:34 +05:30
|
|
|
|
2012-01-31 01:46:19 +05:30
|
|
|
!$ call GET_ENVIRONMENT_VARIABLE(NAME='DAMASK_NUM_THREADS',VALUE=DAMASK_NumThreadsString,STATUS=gotDAMASK_NUM_THREADS) ! get environment variable DAMASK_NUM_THREADS...
|
2014-02-28 16:00:07 +05:30
|
|
|
!$ if(gotDAMASK_NUM_THREADS /= 0) then ! could not get number of threads, set it to 1
|
2019-06-11 18:09:51 +05:30
|
|
|
!$ call IO_warning(35,ext_msg='BEGIN:'//DAMASK_NumThreadsString//':END')
|
2016-12-23 18:50:29 +05:30
|
|
|
!$ DAMASK_NumThreadsInt = 1_4
|
2014-02-28 16:00:07 +05:30
|
|
|
!$ else
|
|
|
|
!$ read(DAMASK_NumThreadsString,'(i6)') DAMASK_NumThreadsInt ! read as integer
|
2016-12-23 18:50:29 +05:30
|
|
|
!$ if (DAMASK_NumThreadsInt < 1_4) DAMASK_NumThreadsInt = 1_4 ! in case of string conversion fails, set it to one
|
2014-02-28 16:00:07 +05:30
|
|
|
!$ endif
|
|
|
|
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution
|
2019-03-09 04:37:57 +05:30
|
|
|
|
|
|
|
inquire(file='numerics.config', exist=fexist)
|
|
|
|
|
|
|
|
fileExists: if (fexist) then
|
2017-04-25 16:04:14 +05:30
|
|
|
write(6,'(a,/)') ' using values from config file'
|
|
|
|
flush(6)
|
2019-03-09 04:37:57 +05:30
|
|
|
fileContent = IO_read_ASCII('numerics.config')
|
|
|
|
do j=1, size(fileContent)
|
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read variables from config file and overwrite default parameters if keyword is present
|
2019-03-09 04:37:57 +05:30
|
|
|
line = fileContent(j)
|
2013-07-31 20:33:38 +05:30
|
|
|
do i=1,len(line)
|
|
|
|
if(line(i:i) == '=') line(i:i) = ' ' ! also allow keyword = value version
|
|
|
|
enddo
|
2013-02-11 15:14:17 +05:30
|
|
|
if (IO_isBlank(line)) cycle ! skip empty lines
|
2015-08-28 13:08:48 +05:30
|
|
|
chunkPos = IO_stringPos(line)
|
2019-06-11 18:09:51 +05:30
|
|
|
tag = IO_lc(IO_stringValue(line,chunkPos,1)) ! extract key
|
2015-08-28 13:08:48 +05:30
|
|
|
|
2012-03-07 15:37:29 +05:30
|
|
|
select case(tag)
|
|
|
|
case ('defgradtolerance')
|
2019-06-11 18:09:51 +05:30
|
|
|
defgradTolerance = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('ijacostiffness')
|
2019-06-11 18:09:51 +05:30
|
|
|
iJacoStiffness = IO_intValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('nmpstate')
|
2019-06-11 18:09:51 +05:30
|
|
|
nMPstate = IO_intValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('substepminhomog')
|
2019-06-11 18:09:51 +05:30
|
|
|
subStepMinHomog = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('substepsizehomog')
|
2019-06-11 18:09:51 +05:30
|
|
|
subStepSizeHomog = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('stepincreasehomog')
|
2019-06-11 18:09:51 +05:30
|
|
|
stepIncreaseHomog = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('integrator')
|
2019-06-11 18:09:51 +05:30
|
|
|
numerics_integrator = IO_intValue(line,chunkPos,2)
|
2013-05-17 23:22:46 +05:30
|
|
|
case ('usepingpong')
|
2019-06-11 18:09:51 +05:30
|
|
|
usepingpong = IO_intValue(line,chunkPos,2) > 0
|
2012-09-24 21:52:25 +05:30
|
|
|
case ('unitlength')
|
2019-06-11 18:09:51 +05:30
|
|
|
numerics_unitlength = IO_floatValue(line,chunkPos,2)
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! RGC parameters
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('atol_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
absTol_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('rtol_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
relTol_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('amax_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
absMax_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('rmax_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
relMax_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('perturbpenalty_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
pPert_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('relevantmismatch_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
xSmoo_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('viscositypower_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
viscPower_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('viscositymodulus_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
viscModus_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('refrelaxationrate_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
refRelaxRate_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('maxrelaxation_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
maxdRelax_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('maxvoldiscrepancy_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
maxVolDiscr_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('voldiscrepancymod_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
volDiscrMod_RGC = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('discrepancypower_rgc')
|
2019-06-11 18:09:51 +05:30
|
|
|
volDiscrPow_RGC = IO_floatValue(line,chunkPos,2)
|
2013-02-11 15:14:17 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-03-28 15:32:11 +05:30
|
|
|
! random seeding parameter
|
2017-11-08 01:26:28 +05:30
|
|
|
case ('random_seed','fixed_seed')
|
2019-06-11 18:09:51 +05:30
|
|
|
randomSeed = IO_intValue(line,chunkPos,2)
|
2013-02-11 15:14:17 +05:30
|
|
|
|
2014-06-25 04:48:07 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! gradient parameter
|
|
|
|
case ('charlength')
|
2019-06-11 18:09:51 +05:30
|
|
|
charLength = IO_floatValue(line,chunkPos,2)
|
2014-12-02 22:47:35 +05:30
|
|
|
case ('residualstiffness')
|
2019-06-11 18:09:51 +05:30
|
|
|
residualStiffness = IO_floatValue(line,chunkPos,2)
|
2014-06-25 04:48:07 +05:30
|
|
|
|
2015-05-28 22:32:23 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! field parameters
|
|
|
|
case ('err_struct_tolabs')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_struct_tolAbs = IO_floatValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('err_struct_tolrel')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_struct_tolRel = IO_floatValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('err_thermal_tolabs')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_thermal_tolabs = IO_floatValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('err_thermal_tolrel')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_thermal_tolrel = IO_floatValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('err_damage_tolabs')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_damage_tolabs = IO_floatValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('err_damage_tolrel')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_damage_tolrel = IO_floatValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('itmax')
|
2019-06-11 18:09:51 +05:30
|
|
|
itmax = IO_intValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('itmin')
|
2019-06-11 18:09:51 +05:30
|
|
|
itmin = IO_intValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('maxcutback')
|
2019-06-11 18:09:51 +05:30
|
|
|
maxCutBack = IO_intValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
case ('maxstaggerediter')
|
2019-06-11 18:09:51 +05:30
|
|
|
stagItMax = IO_intValue(line,chunkPos,2)
|
2015-05-28 22:32:23 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! spectral parameters
|
2019-03-23 13:57:58 +05:30
|
|
|
#ifdef Grid
|
2013-08-07 22:50:05 +05:30
|
|
|
case ('err_div_tolabs')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_div_tolAbs = IO_floatValue(line,chunkPos,2)
|
2013-08-07 22:50:05 +05:30
|
|
|
case ('err_div_tolrel')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_div_tolRel = IO_floatValue(line,chunkPos,2)
|
2012-03-07 15:37:29 +05:30
|
|
|
case ('err_stress_tolrel')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_stress_tolrel = IO_floatValue(line,chunkPos,2)
|
2012-04-11 18:27:25 +05:30
|
|
|
case ('err_stress_tolabs')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_stress_tolabs = IO_floatValue(line,chunkPos,2)
|
2012-08-29 00:49:47 +05:30
|
|
|
case ('petsc_options')
|
2015-08-28 13:08:48 +05:30
|
|
|
petsc_options = trim(line(chunkPos(4):))
|
2013-08-07 22:50:05 +05:30
|
|
|
case ('err_curl_tolabs')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_curl_tolAbs = IO_floatValue(line,chunkPos,2)
|
2013-08-07 22:50:05 +05:30
|
|
|
case ('err_curl_tolrel')
|
2019-06-11 18:09:51 +05:30
|
|
|
err_curl_tolRel = IO_floatValue(line,chunkPos,2)
|
2013-02-28 23:05:02 +05:30
|
|
|
case ('polaralpha')
|
2019-06-11 18:09:51 +05:30
|
|
|
polarAlpha = IO_floatValue(line,chunkPos,2)
|
2013-02-28 23:05:02 +05:30
|
|
|
case ('polarbeta')
|
2019-06-11 18:09:51 +05:30
|
|
|
polarBeta = IO_floatValue(line,chunkPos,2)
|
2012-06-15 21:40:21 +05:30
|
|
|
#endif
|
2014-06-06 06:08:29 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! FEM parameters
|
|
|
|
#ifdef FEM
|
|
|
|
case ('integrationorder')
|
2019-06-11 18:09:51 +05:30
|
|
|
integrationorder = IO_intValue(line,chunkPos,2)
|
2014-06-06 06:08:29 +05:30
|
|
|
case ('structorder')
|
2019-06-11 18:09:51 +05:30
|
|
|
structorder = IO_intValue(line,chunkPos,2)
|
2015-06-09 18:58:50 +05:30
|
|
|
case ('petsc_options')
|
2015-08-28 13:08:48 +05:30
|
|
|
petsc_options = trim(line(chunkPos(4):))
|
2014-12-08 21:57:23 +05:30
|
|
|
case ('bbarstabilisation')
|
2019-06-11 18:09:51 +05:30
|
|
|
BBarStabilisation = IO_intValue(line,chunkPos,2) > 0
|
2014-06-06 06:08:29 +05:30
|
|
|
#endif
|
2018-10-09 02:31:27 +05:30
|
|
|
end select
|
2012-03-07 15:37:29 +05:30
|
|
|
enddo
|
2013-02-11 15:14:17 +05:30
|
|
|
|
2019-03-25 14:06:59 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
else fileExists
|
|
|
|
write(6,'(a,/)') ' using standard values'
|
2014-02-06 16:11:34 +05:30
|
|
|
flush(6)
|
2013-02-11 15:14:17 +05:30
|
|
|
endif fileExists
|
|
|
|
|
2012-11-28 00:06:55 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-03-28 15:32:11 +05:30
|
|
|
! writing parameters to output
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,es8.1)') ' defgradTolerance: ',defgradTolerance
|
|
|
|
write(6,'(a24,1x,i8)') ' iJacoStiffness: ',iJacoStiffness
|
2019-02-23 01:07:41 +05:30
|
|
|
write(6,'(a24,1x,i8)') ' integrator: ',numerics_integrator
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,L8)') ' use ping pong scheme: ',usepingpong
|
|
|
|
write(6,'(a24,1x,es8.1,/)')' unitlength: ',numerics_unitlength
|
2013-03-28 15:32:11 +05:30
|
|
|
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,es8.1)') ' subStepMinHomog: ',subStepMinHomog
|
|
|
|
write(6,'(a24,1x,es8.1)') ' subStepSizeHomog: ',subStepSizeHomog
|
|
|
|
write(6,'(a24,1x,es8.1)') ' stepIncreaseHomog: ',stepIncreaseHomog
|
|
|
|
write(6,'(a24,1x,i8,/)') ' nMPstate: ',nMPstate
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! RGC parameters
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,es8.1)') ' aTol_RGC: ',absTol_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' rTol_RGC: ',relTol_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' aMax_RGC: ',absMax_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' rMax_RGC: ',relMax_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' perturbPenalty_RGC: ',pPert_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' relevantMismatch_RGC: ',xSmoo_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' viscosityrate_RGC: ',viscPower_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' viscositymodulus_RGC: ',viscModus_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' maxrelaxation_RGC: ',maxdRelax_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' maxVolDiscrepancy_RGC: ',maxVolDiscr_RGC
|
|
|
|
write(6,'(a24,1x,es8.1)') ' volDiscrepancyMod_RGC: ',volDiscrMod_RGC
|
|
|
|
write(6,'(a24,1x,es8.1,/)') ' discrepancyPower_RGC: ',volDiscrPow_RGC
|
2013-02-11 15:14:17 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! Random seeding parameter
|
2018-10-09 02:31:27 +05:30
|
|
|
write(6,'(a16,1x,i16,/)') ' random_seed: ',randomSeed
|
2019-06-11 18:09:51 +05:30
|
|
|
if (randomSeed <= 0) &
|
2017-11-08 01:26:28 +05:30
|
|
|
write(6,'(a,/)') ' random seed will be generated!'
|
2014-11-03 16:06:07 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! gradient parameter
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,es8.1)') ' charLength: ',charLength
|
|
|
|
write(6,'(a24,1x,es8.1)') ' residualStiffness: ',residualStiffness
|
2014-11-03 16:06:07 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! openMP parameter
|
2016-06-29 20:05:49 +05:30
|
|
|
!$ write(6,'(a24,1x,i8,/)') ' number of threads: ',DAMASK_NumThreadsInt
|
2010-10-13 21:34:44 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2015-05-28 22:32:23 +05:30
|
|
|
! field parameters
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,i8)') ' itmax: ',itmax
|
|
|
|
write(6,'(a24,1x,i8)') ' itmin: ',itmin
|
|
|
|
write(6,'(a24,1x,i8)') ' maxCutBack: ',maxCutBack
|
|
|
|
write(6,'(a24,1x,i8)') ' maxStaggeredIter: ',stagItMax
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_struct_tolAbs: ',err_struct_tolAbs
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_struct_tolRel: ',err_struct_tolRel
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_thermal_tolabs: ',err_thermal_tolabs
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_thermal_tolrel: ',err_thermal_tolrel
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_damage_tolabs: ',err_damage_tolabs
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_damage_tolrel: ',err_damage_tolrel
|
2015-05-28 22:32:23 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! spectral parameters
|
2019-03-23 13:57:58 +05:30
|
|
|
#ifdef Grid
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,es8.1)') ' err_stress_tolAbs: ',err_stress_tolAbs
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_stress_tolRel: ',err_stress_tolRel
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_div_tolAbs: ',err_div_tolAbs
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_div_tolRel: ',err_div_tolRel
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_curl_tolAbs: ',err_curl_tolAbs
|
|
|
|
write(6,'(a24,1x,es8.1)') ' err_curl_tolRel: ',err_curl_tolRel
|
|
|
|
write(6,'(a24,1x,es8.1)') ' polarAlpha: ',polarAlpha
|
|
|
|
write(6,'(a24,1x,es8.1)') ' polarBeta: ',polarBeta
|
2020-01-26 16:16:14 +05:30
|
|
|
write(6,'(a24,1x,a)') ' PETSc_options: ',trim(petsc_options)
|
2012-08-29 00:49:47 +05:30
|
|
|
#endif
|
2010-12-02 16:34:29 +05:30
|
|
|
|
2014-06-06 06:08:29 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! spectral parameters
|
|
|
|
#ifdef FEM
|
2016-06-29 20:05:49 +05:30
|
|
|
write(6,'(a24,1x,i8)') ' integrationOrder: ',integrationOrder
|
|
|
|
write(6,'(a24,1x,i8)') ' structOrder: ',structOrder
|
|
|
|
write(6,'(a24,1x,a)') ' PETSc_options: ',trim(petsc_defaultOptions)//' '//trim(petsc_options)
|
|
|
|
write(6,'(a24,1x,L8)') ' B-Bar stabilisation: ',BBarStabilisation
|
2014-06-06 06:08:29 +05:30
|
|
|
#endif
|
2014-10-10 18:38:34 +05:30
|
|
|
|
2014-06-06 06:08:29 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! sanity checks
|
2019-06-11 18:09:51 +05:30
|
|
|
if (defgradTolerance <= 0.0_pReal) call IO_error(301,ext_msg='defgradTolerance')
|
|
|
|
if (iJacoStiffness < 1) call IO_error(301,ext_msg='iJacoStiffness')
|
|
|
|
if (nMPstate < 1) call IO_error(301,ext_msg='nMPstate')
|
|
|
|
if (subStepMinHomog <= 0.0_pReal) call IO_error(301,ext_msg='subStepMinHomog')
|
|
|
|
if (subStepSizeHomog <= 0.0_pReal) call IO_error(301,ext_msg='subStepSizeHomog')
|
|
|
|
if (stepIncreaseHomog <= 0.0_pReal) call IO_error(301,ext_msg='stepIncreaseHomog')
|
|
|
|
if (numerics_integrator <= 0 .or. numerics_integrator >= 6) &
|
|
|
|
call IO_error(301,ext_msg='integrator')
|
|
|
|
if (numerics_unitlength <= 0.0_pReal) call IO_error(301,ext_msg='unitlength')
|
|
|
|
if (absTol_RGC <= 0.0_pReal) call IO_error(301,ext_msg='absTol_RGC')
|
|
|
|
if (relTol_RGC <= 0.0_pReal) call IO_error(301,ext_msg='relTol_RGC')
|
|
|
|
if (absMax_RGC <= 0.0_pReal) call IO_error(301,ext_msg='absMax_RGC')
|
|
|
|
if (relMax_RGC <= 0.0_pReal) call IO_error(301,ext_msg='relMax_RGC')
|
|
|
|
if (pPert_RGC <= 0.0_pReal) call IO_error(301,ext_msg='pPert_RGC')
|
|
|
|
if (xSmoo_RGC <= 0.0_pReal) call IO_error(301,ext_msg='xSmoo_RGC')
|
|
|
|
if (viscPower_RGC < 0.0_pReal) call IO_error(301,ext_msg='viscPower_RGC')
|
|
|
|
if (viscModus_RGC < 0.0_pReal) call IO_error(301,ext_msg='viscModus_RGC')
|
|
|
|
if (refRelaxRate_RGC <= 0.0_pReal) call IO_error(301,ext_msg='refRelaxRate_RGC')
|
|
|
|
if (maxdRelax_RGC <= 0.0_pReal) call IO_error(301,ext_msg='maxdRelax_RGC')
|
|
|
|
if (maxVolDiscr_RGC <= 0.0_pReal) call IO_error(301,ext_msg='maxVolDiscr_RGC')
|
|
|
|
if (volDiscrMod_RGC < 0.0_pReal) call IO_error(301,ext_msg='volDiscrMod_RGC')
|
|
|
|
if (volDiscrPow_RGC <= 0.0_pReal) call IO_error(301,ext_msg='volDiscrPw_RGC')
|
|
|
|
if (residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness')
|
|
|
|
if (itmax <= 1) call IO_error(301,ext_msg='itmax')
|
|
|
|
if (itmin > itmax .or. itmin < 1) call IO_error(301,ext_msg='itmin')
|
|
|
|
if (maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
|
|
|
|
if (stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter')
|
|
|
|
if (err_struct_tolRel <= 0.0_pReal) call IO_error(301,ext_msg='err_struct_tolRel')
|
|
|
|
if (err_struct_tolAbs <= 0.0_pReal) call IO_error(301,ext_msg='err_struct_tolAbs')
|
|
|
|
if (err_thermal_tolabs <= 0.0_pReal) call IO_error(301,ext_msg='err_thermal_tolabs')
|
|
|
|
if (err_thermal_tolrel <= 0.0_pReal) call IO_error(301,ext_msg='err_thermal_tolrel')
|
|
|
|
if (err_damage_tolabs <= 0.0_pReal) call IO_error(301,ext_msg='err_damage_tolabs')
|
|
|
|
if (err_damage_tolrel <= 0.0_pReal) call IO_error(301,ext_msg='err_damage_tolrel')
|
2019-03-23 13:57:58 +05:30
|
|
|
#ifdef Grid
|
2019-06-11 18:09:51 +05:30
|
|
|
if (err_stress_tolrel <= 0.0_pReal) call IO_error(301,ext_msg='err_stress_tolRel')
|
|
|
|
if (err_stress_tolabs <= 0.0_pReal) call IO_error(301,ext_msg='err_stress_tolAbs')
|
|
|
|
if (err_div_tolRel < 0.0_pReal) call IO_error(301,ext_msg='err_div_tolRel')
|
|
|
|
if (err_div_tolAbs <= 0.0_pReal) call IO_error(301,ext_msg='err_div_tolAbs')
|
|
|
|
if (err_curl_tolRel < 0.0_pReal) call IO_error(301,ext_msg='err_curl_tolRel')
|
|
|
|
if (err_curl_tolAbs <= 0.0_pReal) call IO_error(301,ext_msg='err_curl_tolAbs')
|
2013-02-28 23:05:02 +05:30
|
|
|
if (polarAlpha <= 0.0_pReal .or. &
|
2019-06-11 18:09:51 +05:30
|
|
|
polarAlpha > 2.0_pReal) call IO_error(301,ext_msg='polarAlpha')
|
2013-08-07 22:50:05 +05:30
|
|
|
if (polarBeta < 0.0_pReal .or. &
|
2019-06-11 18:09:51 +05:30
|
|
|
polarBeta > 2.0_pReal) call IO_error(301,ext_msg='polarBeta')
|
2012-08-29 00:49:47 +05:30
|
|
|
#endif
|
2012-03-07 15:37:29 +05:30
|
|
|
|
|
|
|
end subroutine numerics_init
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2012-03-07 15:37:29 +05:30
|
|
|
end module numerics
|