2011-04-07 12:50:28 +05:30
|
|
|
! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! This file is part of DAMASK,
|
2011-04-07 12:50:28 +05:30
|
|
|
! the Düsseldorf Advanced MAterial Simulation Kit.
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! DAMASK is free software: you can redistribute it and/or modify
|
|
|
|
! it under the terms of the GNU General Public License as published by
|
|
|
|
! the Free Software Foundation, either version 3 of the License, or
|
|
|
|
! (at your option) any later version.
|
|
|
|
!
|
|
|
|
! DAMASK is distributed in the hope that it will be useful,
|
|
|
|
! but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
! GNU General Public License for more details.
|
|
|
|
!
|
|
|
|
! You should have received a copy of the GNU General Public License
|
|
|
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
|
|
|
!
|
|
|
|
!##############################################################
|
2009-08-31 20:39:15 +05:30
|
|
|
!* $Id$
|
2009-06-15 18:41:21 +05:30
|
|
|
!##############################################################
|
|
|
|
MODULE numerics
|
|
|
|
!##############################################################
|
|
|
|
|
|
|
|
use prec, only: pInt, pReal
|
2011-12-01 17:31:13 +05:30
|
|
|
use IO, only: IO_warning
|
2009-06-15 18:41:21 +05:30
|
|
|
implicit none
|
|
|
|
|
|
|
|
character(len=64), parameter :: numerics_configFile = 'numerics.config' ! name of configuration file
|
2011-10-24 23:56:34 +05:30
|
|
|
integer(pInt) :: iJacoStiffness, & ! frequency of stiffness update
|
2009-06-15 18:41:21 +05:30
|
|
|
iJacoLpresiduum, & ! frequency of Jacobian update of residuum in Lp
|
2009-10-26 22:13:43 +05:30
|
|
|
nHomog, & ! homogenization loop limit (only for debugging info, loop limit is determined by "subStepMinHomog")
|
2009-08-11 22:01:57 +05:30
|
|
|
nMPstate, & ! materialpoint state loop limit
|
2009-10-26 22:13:43 +05:30
|
|
|
nCryst, & ! crystallite loop limit (only for debugging info, loop limit is determined by "subStepMinCryst")
|
2009-06-15 18:41:21 +05:30
|
|
|
nState, & ! state loop limit
|
2009-11-10 19:06:27 +05:30
|
|
|
nStress, & ! stress loop limit
|
2010-10-01 17:48:49 +05:30
|
|
|
pert_method, & ! method used in perturbation technique for tangent
|
2011-02-23 18:00:52 +05:30
|
|
|
numerics_integrationMode ! integration mode 1 = central solution ; integration mode 2 = perturbation
|
|
|
|
integer(pInt), dimension(2) :: numerics_integrator ! method used for state integration (central & perturbed state)
|
2011-10-24 23:56:34 +05:30
|
|
|
real(pReal) :: relevantStrain, & ! strain increment considered significant (used by crystallite to determine whether strain inc is considered significant)
|
2010-05-20 20:25:11 +05:30
|
|
|
defgradTolerance, & ! deviation of deformation gradient that is still allowed (used by CPFEM to determine outdated ffn1)
|
2009-06-15 18:41:21 +05:30
|
|
|
pert_Fg, & ! strain perturbation for FEM Jacobi
|
2009-10-26 22:13:43 +05:30
|
|
|
subStepMinCryst, & ! minimum (relative) size of sub-step allowed during cutback in crystallite
|
|
|
|
subStepMinHomog, & ! minimum (relative) size of sub-step allowed during cutback in homogenization
|
2009-11-10 19:06:27 +05:30
|
|
|
subStepSizeCryst, & ! size of first substep when cutback in crystallite
|
|
|
|
subStepSizeHomog, & ! size of first substep when cutback in homogenization
|
|
|
|
stepIncreaseCryst, & ! increase of next substep size when previous substep converged in crystallite
|
|
|
|
stepIncreaseHomog, & ! increase of next substep size when previous substep converged in homogenization
|
2009-07-22 21:37:19 +05:30
|
|
|
rTol_crystalliteState, & ! relative tolerance in crystallite state loop
|
|
|
|
rTol_crystalliteTemperature, & ! relative tolerance in crystallite temperature loop
|
2009-06-15 18:41:21 +05:30
|
|
|
rTol_crystalliteStress, & ! relative tolerance in crystallite stress loop
|
|
|
|
aTol_crystalliteStress, & ! absolute tolerance in crystallite stress loop
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2009-12-16 21:50:53 +05:30
|
|
|
!* RGC parameters: added <<<updated 17.12.2009>>>
|
2009-07-31 17:32:20 +05:30
|
|
|
absTol_RGC, & ! absolute tolerance of RGC residuum
|
|
|
|
relTol_RGC, & ! relative tolerance of RGC residuum
|
|
|
|
absMax_RGC, & ! absolute maximum of RGC residuum
|
|
|
|
relMax_RGC, & ! relative maximum of RGC residuum
|
|
|
|
pPert_RGC, & ! perturbation for computing RGC penalty tangent
|
2009-11-17 19:12:38 +05:30
|
|
|
xSmoo_RGC, & ! RGC penalty smoothing parameter (hyperbolic tangent)
|
2010-03-24 18:50:12 +05:30
|
|
|
viscPower_RGC, & ! power (sensitivity rate) of numerical viscosity in RGC scheme
|
2009-11-17 19:12:38 +05:30
|
|
|
viscModus_RGC, & ! stress modulus of RGC numerical viscosity
|
2010-03-24 18:50:12 +05:30
|
|
|
refRelaxRate_RGC, & ! reference relaxation rate in RGC viscosity
|
2009-12-16 21:50:53 +05:30
|
|
|
maxdRelax_RGC, & ! threshold of maximum relaxation vector increment (if exceed this then cutback)
|
|
|
|
maxVolDiscr_RGC, & ! threshold of maximum volume discrepancy allowed
|
|
|
|
volDiscrMod_RGC, & ! stiffness of RGC volume discrepancy (zero = without volume discrepancy constraint)
|
2010-10-13 21:34:44 +05:30
|
|
|
volDiscrPow_RGC, & ! powerlaw penalty for volume discrepancy
|
|
|
|
!* spectral parameters:
|
2011-01-31 22:37:42 +05:30
|
|
|
err_div_tol, & ! error of divergence in fourier space
|
2011-10-18 14:46:18 +05:30
|
|
|
err_stress_tolrel, & ! factor to multiply with highest stress to get err_stress_tol
|
2011-10-24 23:56:34 +05:30
|
|
|
fftw_timelimit, & ! sets the timelimit of plan creation for FFTW, see manual on www.fftw.org
|
2011-10-25 19:08:24 +05:30
|
|
|
rotation_tol ! tolerance of rotation specified in loadcase
|
2011-12-01 17:31:13 +05:30
|
|
|
character(len=64) :: fftw_planner_string ! reads the planing-rigor flag, see manual on www.fftw.org
|
2012-01-13 21:48:16 +05:30
|
|
|
integer(pInt) :: fftw_planner_flag ! conversion of fftw_planner_string to integer, basically what is usually done in the include file of fftw
|
2011-11-15 23:24:18 +05:30
|
|
|
logical :: memory_efficient,& ! for fast execution (pre calculation of gamma_hat)
|
2012-01-25 14:26:46 +05:30
|
|
|
divergence_correction,& ! correct divergence calculation in fourier space
|
|
|
|
update_gamma,& ! update gamma operator with current stiffness
|
|
|
|
simplified_algorithm ! use short algorithm without fluctuation field
|
|
|
|
real(pReal) :: cut_off_value ! percentage of frequencies to cut away
|
2011-11-15 23:24:18 +05:30
|
|
|
integer(pInt) :: itmax , & ! maximum number of iterations
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2011-02-07 20:05:42 +05:30
|
|
|
|
2011-01-31 22:37:42 +05:30
|
|
|
!* Random seeding parameters
|
|
|
|
fixedSeed ! fixed seeding for pseudo-random number generator
|
|
|
|
!* OpenMP variable
|
2011-09-13 21:27:58 +05:30
|
|
|
integer(pInt) DAMASK_NumThreadsInt ! value stored in environment variable DAMASK_NUM_THREADS
|
2010-12-02 16:34:29 +05:30
|
|
|
|
2009-11-10 19:06:27 +05:30
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
CONTAINS
|
|
|
|
|
|
|
|
!*******************************************
|
|
|
|
! initialization subroutine
|
|
|
|
!*******************************************
|
|
|
|
subroutine numerics_init()
|
|
|
|
|
|
|
|
!*** variables and functions from other modules ***!
|
|
|
|
use prec, only: pInt, &
|
|
|
|
pReal
|
|
|
|
use IO, only: IO_error, &
|
|
|
|
IO_open_file, &
|
|
|
|
IO_isBlank, &
|
|
|
|
IO_stringPos, &
|
|
|
|
IO_stringValue, &
|
|
|
|
IO_lc, &
|
|
|
|
IO_floatValue, &
|
|
|
|
IO_intValue
|
2010-12-02 16:34:29 +05:30
|
|
|
!$ use OMP_LIB ! the openMP function library
|
2009-06-15 18:41:21 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
!*** input variables ***!
|
|
|
|
|
|
|
|
!*** output variables ***!
|
|
|
|
|
|
|
|
!*** local variables ***!
|
|
|
|
integer(pInt), parameter :: fileunit = 300
|
|
|
|
integer(pInt), parameter :: maxNchunks = 2
|
|
|
|
integer(pInt), dimension(1+2*maxNchunks) :: positions
|
|
|
|
character(len=64) tag
|
|
|
|
character(len=1024) line
|
|
|
|
|
2010-12-02 16:34:29 +05:30
|
|
|
! OpenMP variable
|
2011-05-28 15:12:25 +05:30
|
|
|
!$ character(len=4) DAMASK_NumThreadsString !environment variable DAMASK_NUM_THREADS
|
2010-12-02 16:34:29 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) '<<<+- numerics init -+>>>'
|
|
|
|
write(6,*) '$Id$'
|
|
|
|
write(6,*)
|
|
|
|
!$OMP END CRITICAL (write2out)
|
2009-06-18 19:58:02 +05:30
|
|
|
|
|
|
|
! initialize all parameters with standard values
|
2009-07-31 17:32:20 +05:30
|
|
|
relevantStrain = 1.0e-7_pReal
|
2010-05-20 20:25:11 +05:30
|
|
|
defgradTolerance = 1.0e-7_pReal
|
2009-07-31 17:32:20 +05:30
|
|
|
iJacoStiffness = 1_pInt
|
|
|
|
iJacoLpresiduum = 1_pInt
|
2009-11-10 19:06:27 +05:30
|
|
|
pert_Fg = 1.0e-7_pReal
|
|
|
|
pert_method = 1
|
2009-08-11 22:01:57 +05:30
|
|
|
nHomog = 20_pInt
|
2009-10-26 22:13:43 +05:30
|
|
|
subStepMinHomog = 1.0e-3_pReal
|
2009-11-10 19:06:27 +05:30
|
|
|
subStepSizeHomog = 0.25
|
|
|
|
stepIncreaseHomog = 1.5
|
2009-08-11 22:01:57 +05:30
|
|
|
nMPstate = 10_pInt
|
2009-07-31 17:32:20 +05:30
|
|
|
nCryst = 20_pInt
|
2009-10-26 22:13:43 +05:30
|
|
|
subStepMinCryst = 1.0e-3_pReal
|
2009-11-10 19:06:27 +05:30
|
|
|
subStepsizeCryst = 0.25
|
|
|
|
stepIncreaseCryst = 1.5
|
2009-07-31 17:32:20 +05:30
|
|
|
nState = 10_pInt
|
|
|
|
nStress = 40_pInt
|
|
|
|
rTol_crystalliteState = 1.0e-6_pReal
|
2009-07-22 21:37:19 +05:30
|
|
|
rTol_crystalliteTemperature = 1.0e-6_pReal
|
2009-07-31 17:32:20 +05:30
|
|
|
rTol_crystalliteStress = 1.0e-6_pReal
|
2009-10-19 18:23:56 +05:30
|
|
|
aTol_crystalliteStress = 1.0e-8_pReal ! residuum is in Lp (hence strain on the order of 1e-8 here)
|
2011-02-23 18:00:52 +05:30
|
|
|
numerics_integrator(1) = 1 ! fix-point iteration
|
|
|
|
numerics_integrator(2) = 1 ! fix-point iteration
|
2010-10-01 17:48:49 +05:30
|
|
|
|
2009-12-16 21:50:53 +05:30
|
|
|
!* RGC parameters: added <<<updated 17.12.2009>>> with moderate setting
|
2009-10-30 15:24:52 +05:30
|
|
|
absTol_RGC = 1.0e+4
|
2009-07-31 17:32:20 +05:30
|
|
|
relTol_RGC = 1.0e-3
|
2009-10-30 15:24:52 +05:30
|
|
|
absMax_RGC = 1.0e+10
|
2009-07-31 17:32:20 +05:30
|
|
|
relMax_RGC = 1.0e+2
|
2009-10-30 15:24:52 +05:30
|
|
|
pPert_RGC = 1.0e-7
|
2009-07-31 17:32:20 +05:30
|
|
|
xSmoo_RGC = 1.0e-5
|
2010-03-24 18:50:12 +05:30
|
|
|
viscPower_RGC = 1.0e+0 ! Newton viscosity (linear model)
|
2009-11-24 20:30:25 +05:30
|
|
|
viscModus_RGC = 0.0e+0 ! No viscosity is applied
|
2010-03-24 18:50:12 +05:30
|
|
|
refRelaxRate_RGC = 1.0e-3
|
2009-11-17 19:12:38 +05:30
|
|
|
maxdRelax_RGC = 1.0e+0
|
2009-12-16 21:50:53 +05:30
|
|
|
maxVolDiscr_RGC = 1.0e-5 ! tolerance for volume discrepancy allowed
|
|
|
|
volDiscrMod_RGC = 1.0e+12
|
|
|
|
volDiscrPow_RGC = 5.0
|
2010-10-13 21:34:44 +05:30
|
|
|
|
|
|
|
!* spectral parameters:
|
2011-10-18 14:46:18 +05:30
|
|
|
err_div_tol = 1.0e-4 ! 1.0e-4 proposed by Suquet
|
|
|
|
err_stress_tolrel = 0.01 ! relative tolerance for fullfillment of stress BC (1% of maximum stress)
|
|
|
|
itmax = 20_pInt ! Maximum iteration number
|
|
|
|
memory_efficient = .true. ! Precalculate Gamma-operator (81 double per point)
|
|
|
|
fftw_timelimit = -1.0_pReal ! no timelimit of plan creation for FFTW
|
2011-12-01 17:31:13 +05:30
|
|
|
fftw_planner_string ='FFTW_PATIENT'
|
2011-10-25 19:08:24 +05:30
|
|
|
rotation_tol = 1.0e-12
|
2012-01-25 14:26:46 +05:30
|
|
|
divergence_correction = .true. ! correct divergence by empirical factor
|
|
|
|
simplified_algorithm = .true. ! use algorithm without fluctuation field
|
|
|
|
update_gamma = .false. ! do not update gamma operator with current stiffness
|
|
|
|
cut_off_value = 0.0_pReal ! use all frequencies
|
|
|
|
|
2011-11-15 23:24:18 +05:30
|
|
|
!* Random seeding parameters
|
2009-08-27 21:00:40 +05:30
|
|
|
fixedSeed = 0_pInt
|
|
|
|
|
2010-12-02 16:34:29 +05:30
|
|
|
|
2011-05-28 15:12:25 +05:30
|
|
|
!* determin number of threads from environment variable DAMASK_NUM_THREADS
|
2011-08-03 23:27:28 +05:30
|
|
|
DAMASK_NumThreadsInt = 0_pInt
|
2011-05-28 15:12:25 +05:30
|
|
|
!$ call GetEnv('DAMASK_NUM_THREADS',DAMASK_NumThreadsString) ! get environment variable DAMASK_NUM_THREADS...
|
|
|
|
!$ read(DAMASK_NumThreadsString,'(i4)') DAMASK_NumThreadsInt ! ...convert it to integer...
|
|
|
|
!$ if (DAMASK_NumThreadsInt < 1) DAMASK_NumThreadsInt = 1 ! ...ensure that its at least one...
|
|
|
|
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! ...and use it as number of threads for parallel execution
|
2010-12-02 16:34:29 +05:30
|
|
|
|
2009-06-18 19:58:02 +05:30
|
|
|
! try to open the config file
|
|
|
|
if(IO_open_file(fileunit,numerics_configFile)) then
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
write(6,*) ' ... using values from config file'
|
|
|
|
write(6,*)
|
|
|
|
!$OMP END CRITICAL (write2out)
|
2009-06-18 19:58:02 +05:30
|
|
|
|
|
|
|
line = ''
|
|
|
|
! read variables from config file and overwrite parameters
|
|
|
|
do
|
|
|
|
read(fileunit,'(a1024)',END=100) line
|
|
|
|
if (IO_isBlank(line)) cycle ! skip empty lines
|
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
|
|
|
|
select case(tag)
|
|
|
|
case ('relevantstrain')
|
|
|
|
relevantStrain = IO_floatValue(line,positions,2)
|
2010-05-20 20:25:11 +05:30
|
|
|
case ('defgradtolerance')
|
|
|
|
defgradTolerance = IO_floatValue(line,positions,2)
|
2009-06-18 19:58:02 +05:30
|
|
|
case ('ijacostiffness')
|
|
|
|
iJacoStiffness = IO_intValue(line,positions,2)
|
|
|
|
case ('ijacolpresiduum')
|
|
|
|
iJacoLpresiduum = IO_intValue(line,positions,2)
|
|
|
|
case ('pert_fg')
|
|
|
|
pert_Fg = IO_floatValue(line,positions,2)
|
2009-11-10 19:06:27 +05:30
|
|
|
case ('pert_method')
|
|
|
|
pert_method = IO_intValue(line,positions,2)
|
2009-06-18 19:58:02 +05:30
|
|
|
case ('nhomog')
|
|
|
|
nHomog = IO_intValue(line,positions,2)
|
2009-08-11 22:01:57 +05:30
|
|
|
case ('nmpstate')
|
|
|
|
nMPstate = IO_intValue(line,positions,2)
|
2009-06-18 19:58:02 +05:30
|
|
|
case ('ncryst')
|
|
|
|
nCryst = IO_intValue(line,positions,2)
|
|
|
|
case ('nstate')
|
|
|
|
nState = IO_intValue(line,positions,2)
|
|
|
|
case ('nstress')
|
|
|
|
nStress = IO_intValue(line,positions,2)
|
2009-10-26 22:13:43 +05:30
|
|
|
case ('substepmincryst')
|
|
|
|
subStepMinCryst = IO_floatValue(line,positions,2)
|
2009-11-10 19:06:27 +05:30
|
|
|
case ('substepsizecryst')
|
|
|
|
subStepSizeCryst = IO_floatValue(line,positions,2)
|
|
|
|
case ('stepincreasecryst')
|
|
|
|
stepIncreaseCryst = IO_floatValue(line,positions,2)
|
2009-10-26 22:13:43 +05:30
|
|
|
case ('substepminhomog')
|
|
|
|
subStepMinHomog = IO_floatValue(line,positions,2)
|
2009-11-10 19:06:27 +05:30
|
|
|
case ('substepsizehomog')
|
|
|
|
subStepSizeHomog = IO_floatValue(line,positions,2)
|
|
|
|
case ('stepincreasehomog')
|
|
|
|
stepIncreaseHomog = IO_floatValue(line,positions,2)
|
2009-06-18 19:58:02 +05:30
|
|
|
case ('rtol_crystallitestate')
|
2009-07-22 21:37:19 +05:30
|
|
|
rTol_crystalliteState = IO_floatValue(line,positions,2)
|
|
|
|
case ('rtol_crystallitetemperature')
|
2009-07-01 16:25:31 +05:30
|
|
|
rTol_crystalliteTemperature = IO_floatValue(line,positions,2)
|
2009-06-18 19:58:02 +05:30
|
|
|
case ('rtol_crystallitestress')
|
|
|
|
rTol_crystalliteStress = IO_floatValue(line,positions,2)
|
|
|
|
case ('atol_crystallitestress')
|
|
|
|
aTol_crystalliteStress = IO_floatValue(line,positions,2)
|
2010-10-01 17:48:49 +05:30
|
|
|
case ('integrator')
|
2011-02-23 18:00:52 +05:30
|
|
|
numerics_integrator(1) = IO_intValue(line,positions,2)
|
2010-10-01 17:48:49 +05:30
|
|
|
case ('integratorstiffness')
|
2011-02-23 18:00:52 +05:30
|
|
|
numerics_integrator(2) = IO_intValue(line,positions,2)
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2011-01-31 22:37:42 +05:30
|
|
|
!* RGC parameters:
|
2009-07-31 17:32:20 +05:30
|
|
|
case ('atol_rgc')
|
|
|
|
absTol_RGC = IO_floatValue(line,positions,2)
|
|
|
|
case ('rtol_rgc')
|
|
|
|
relTol_RGC = IO_floatValue(line,positions,2)
|
|
|
|
case ('amax_rgc')
|
|
|
|
absMax_RGC = IO_floatValue(line,positions,2)
|
|
|
|
case ('rmax_rgc')
|
|
|
|
relMax_RGC = IO_floatValue(line,positions,2)
|
|
|
|
case ('perturbpenalty_rgc')
|
|
|
|
pPert_RGC = IO_floatValue(line,positions,2)
|
|
|
|
case ('relevantmismatch_rgc')
|
|
|
|
xSmoo_RGC = IO_floatValue(line,positions,2)
|
2010-03-24 18:50:12 +05:30
|
|
|
case ('viscositypower_rgc')
|
|
|
|
viscPower_RGC = IO_floatValue(line,positions,2)
|
2009-11-17 19:12:38 +05:30
|
|
|
case ('viscositymodulus_rgc')
|
2009-11-24 20:30:25 +05:30
|
|
|
viscModus_RGC = IO_floatValue(line,positions,2)
|
2010-03-24 18:50:12 +05:30
|
|
|
case ('refrelaxationrate_rgc')
|
|
|
|
refRelaxRate_RGC = IO_floatValue(line,positions,2)
|
2009-11-17 19:12:38 +05:30
|
|
|
case ('maxrelaxation_rgc')
|
|
|
|
maxdRelax_RGC = IO_floatValue(line,positions,2)
|
2009-12-16 21:50:53 +05:30
|
|
|
case ('maxvoldiscrepancy_rgc')
|
|
|
|
maxVolDiscr_RGC = IO_floatValue(line,positions,2)
|
|
|
|
case ('voldiscrepancymod_rgc')
|
|
|
|
volDiscrMod_RGC = IO_floatValue(line,positions,2)
|
|
|
|
case ('discrepancypower_rgc')
|
|
|
|
volDiscrPow_RGC = IO_floatValue(line,positions,2)
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2010-10-13 21:34:44 +05:30
|
|
|
!* spectral parameters
|
2011-01-31 22:37:42 +05:30
|
|
|
case ('err_div_tol')
|
|
|
|
err_div_tol = IO_floatValue(line,positions,2)
|
|
|
|
case ('err_stress_tolrel')
|
|
|
|
err_stress_tolrel = IO_floatValue(line,positions,2)
|
|
|
|
case ('itmax')
|
|
|
|
itmax = IO_intValue(line,positions,2)
|
2011-02-21 20:07:38 +05:30
|
|
|
case ('memory_efficient')
|
|
|
|
memory_efficient = IO_intValue(line,positions,2) > 0_pInt
|
2011-10-18 14:46:18 +05:30
|
|
|
case ('fftw_timelimit')
|
|
|
|
fftw_timelimit = IO_floatValue(line,positions,2)
|
2011-12-01 17:31:13 +05:30
|
|
|
case ('fftw_planner_string')
|
|
|
|
fftw_planner_string = IO_stringValue(line,positions,2)
|
2011-10-25 19:08:24 +05:30
|
|
|
case ('rotation_tol')
|
|
|
|
rotation_tol = IO_floatValue(line,positions,2)
|
2011-11-15 23:24:18 +05:30
|
|
|
case ('divergence_correction')
|
|
|
|
divergence_correction = IO_intValue(line,positions,2) > 0_pInt
|
2012-01-25 14:26:46 +05:30
|
|
|
case ('update_gamma')
|
|
|
|
update_gamma = IO_intValue(line,positions,2) > 0_pInt
|
|
|
|
case ('simplified_algorithm')
|
|
|
|
simplified_algorithm = IO_intValue(line,positions,2) > 0_pInt
|
|
|
|
case ('cut_off_value')
|
|
|
|
cut_off_value = IO_floatValue(line,positions,2)
|
2010-10-13 21:34:44 +05:30
|
|
|
|
2011-01-31 22:37:42 +05:30
|
|
|
!* Random seeding parameters
|
2009-08-27 21:00:40 +05:30
|
|
|
case ('fixed_seed')
|
2011-11-04 15:59:35 +05:30
|
|
|
fixedSeed = IO_intValue(line,positions,2)
|
2009-06-18 19:58:02 +05:30
|
|
|
endselect
|
|
|
|
enddo
|
|
|
|
100 close(fileunit)
|
|
|
|
|
|
|
|
! no config file, so we use standard values
|
|
|
|
else
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
write(6,*) ' ... using standard values'
|
|
|
|
write(6,*)
|
|
|
|
!$OMP END CRITICAL (write2out)
|
2009-06-18 19:58:02 +05:30
|
|
|
|
|
|
|
endif
|
2011-12-01 17:31:13 +05:30
|
|
|
select case(IO_lc(fftw_planner_string)) ! setting parameters for the plan creation of FFTW. Basically a translation from fftw3.f
|
|
|
|
case('estimate','fftw_estimate') ! ordered from slow execution (but fast plan creation) to fast execution
|
|
|
|
fftw_planner_flag = 64
|
|
|
|
case('measure','fftw_measure')
|
|
|
|
fftw_planner_flag = 0
|
|
|
|
case('patient','fftw_patient')
|
|
|
|
fftw_planner_flag= 32
|
|
|
|
case('exhaustive','fftw_exhaustive')
|
|
|
|
fftw_planner_flag = 8
|
|
|
|
case default
|
|
|
|
call IO_warning(warning_ID=47_pInt,ext_msg=trim(IO_lc(fftw_planner_string)))
|
|
|
|
fftw_planner_flag = 32
|
|
|
|
end select
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2009-06-18 19:58:02 +05:30
|
|
|
! writing parameters to output file
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP CRITICAL (write2out)
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,e8.1)') ' relevantStrain: ',relevantStrain
|
|
|
|
write(6,'(a24,x,e8.1)') ' defgradTolerance: ',defgradTolerance
|
|
|
|
write(6,'(a24,x,i8)') ' iJacoStiffness: ',iJacoStiffness
|
|
|
|
write(6,'(a24,x,i8)') ' iJacoLpresiduum: ',iJacoLpresiduum
|
|
|
|
write(6,'(a24,x,e8.1)') ' pert_Fg: ',pert_Fg
|
|
|
|
write(6,'(a24,x,i8)') ' pert_method: ',pert_method
|
|
|
|
write(6,'(a24,x,i8)') ' nCryst: ',nCryst
|
|
|
|
write(6,'(a24,x,e8.1)') ' subStepMinCryst: ',subStepMinCryst
|
|
|
|
write(6,'(a24,x,e8.1)') ' subStepSizeCryst: ',subStepSizeCryst
|
|
|
|
write(6,'(a24,x,e8.1)') ' stepIncreaseCryst: ',stepIncreaseCryst
|
|
|
|
write(6,'(a24,x,i8)') ' nState: ',nState
|
|
|
|
write(6,'(a24,x,i8)') ' nStress: ',nStress
|
|
|
|
write(6,'(a24,x,e8.1)') ' rTol_crystalliteState: ',rTol_crystalliteState
|
|
|
|
write(6,'(a24,x,e8.1)') ' rTol_crystalliteTemp: ',rTol_crystalliteTemperature
|
|
|
|
write(6,'(a24,x,e8.1)') ' rTol_crystalliteStress: ',rTol_crystalliteStress
|
|
|
|
write(6,'(a24,x,e8.1)') ' aTol_crystalliteStress: ',aTol_crystalliteStress
|
|
|
|
write(6,'(a24,2(x,i8),/)')' integrator: ',numerics_integrator
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,i8)') ' nHomog: ',nHomog
|
|
|
|
write(6,'(a24,x,e8.1)') ' subStepMinHomog: ',subStepMinHomog
|
|
|
|
write(6,'(a24,x,e8.1)') ' subStepSizeHomog: ',subStepSizeHomog
|
|
|
|
write(6,'(a24,x,e8.1)') ' stepIncreaseHomog: ',stepIncreaseHomog
|
|
|
|
write(6,'(a24,x,i8,/)') ' nMPstate: ',nMPstate
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2010-10-13 21:34:44 +05:30
|
|
|
!* RGC parameters
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,e8.1)') ' aTol_RGC: ',absTol_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' rTol_RGC: ',relTol_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' aMax_RGC: ',absMax_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' rMax_RGC: ',relMax_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' perturbPenalty_RGC: ',pPert_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' relevantMismatch_RGC: ',xSmoo_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' viscosityrate_RGC: ',viscPower_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' viscositymodulus_RGC: ',viscModus_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' maxrelaxation_RGC: ',maxdRelax_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' maxVolDiscrepancy_RGC: ',maxVolDiscr_RGC
|
|
|
|
write(6,'(a24,x,e8.1)') ' volDiscrepancyMod_RGC: ',volDiscrMod_RGC
|
|
|
|
write(6,'(a24,x,e8.1,/)') ' discrepancyPower_RGC: ',volDiscrPow_RGC
|
2010-10-13 21:34:44 +05:30
|
|
|
|
|
|
|
!* spectral parameters
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,e8.1)') ' err_div_tol: ',err_div_tol
|
|
|
|
write(6,'(a24,x,e8.1)') ' err_stress_tolrel: ',err_stress_tolrel
|
|
|
|
write(6,'(a24,x,i8)') ' itmax: ',itmax
|
|
|
|
write(6,'(a24,x,L8)') ' memory_efficient: ',memory_efficient
|
2012-01-25 14:26:46 +05:30
|
|
|
if(fftw_timelimit<0.0_pReal) then
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,L8)') ' fftw_timelimit: ',.false.
|
2011-10-18 14:46:18 +05:30
|
|
|
else
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,e8.1)') ' fftw_timelimit: ',fftw_timelimit
|
2011-10-18 14:46:18 +05:30
|
|
|
endif
|
2011-12-01 17:31:13 +05:30
|
|
|
write(6,'(a24,x,a)') ' fftw_planner_string: ',trim(fftw_planner_string)
|
|
|
|
write(6,'(a24,x,i8)') ' fftw_planner_flag: ',fftw_planner_flag
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,e8.1)') ' rotation_tol: ',rotation_tol
|
|
|
|
write(6,'(a24,x,L8,/)') ' divergence_correction: ',divergence_correction
|
2012-01-25 14:26:46 +05:30
|
|
|
write(6,'(a24,x,L8,/)') ' update_gamma: ',update_gamma
|
|
|
|
write(6,'(a24,x,L8,/)') ' simplified_algorithm: ',simplified_algorithm
|
|
|
|
write(6,'(a24,x,e8.1)') ' cut_off_value: ',cut_off_value
|
2010-10-13 21:34:44 +05:30
|
|
|
!* Random seeding parameters
|
2011-11-15 23:24:18 +05:30
|
|
|
write(6,'(a24,x,i16,/)') ' fixed_seed: ',fixedSeed
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP END CRITICAL (write2out)
|
2010-12-02 16:34:29 +05:30
|
|
|
|
|
|
|
!* openMP parameter
|
2011-11-15 23:24:18 +05:30
|
|
|
!$ write(6,'(a24,x,i8,/)') ' number of threads: ',DAMASK_NumThreadsInt
|
2009-06-18 19:58:02 +05:30
|
|
|
|
2009-07-31 17:32:20 +05:30
|
|
|
! sanity check
|
|
|
|
if (relevantStrain <= 0.0_pReal) call IO_error(260)
|
2010-05-20 20:25:11 +05:30
|
|
|
if (defgradTolerance <= 0.0_pReal) call IO_error(294)
|
2009-07-31 17:32:20 +05:30
|
|
|
if (iJacoStiffness < 1_pInt) call IO_error(261)
|
|
|
|
if (iJacoLpresiduum < 1_pInt) call IO_error(262)
|
|
|
|
if (pert_Fg <= 0.0_pReal) call IO_error(263)
|
2009-11-10 19:06:27 +05:30
|
|
|
if (pert_method <= 0_pInt .or. pert_method >= 4_pInt) &
|
|
|
|
call IO_error(299)
|
2009-07-31 17:32:20 +05:30
|
|
|
if (nHomog < 1_pInt) call IO_error(264)
|
2009-08-11 22:01:57 +05:30
|
|
|
if (nMPstate < 1_pInt) call IO_error(279) !! missing in IO !!
|
2009-07-31 17:32:20 +05:30
|
|
|
if (nCryst < 1_pInt) call IO_error(265)
|
|
|
|
if (nState < 1_pInt) call IO_error(266)
|
|
|
|
if (nStress < 1_pInt) call IO_error(267)
|
2009-10-26 22:13:43 +05:30
|
|
|
if (subStepMinCryst <= 0.0_pReal) call IO_error(268)
|
2009-11-10 19:06:27 +05:30
|
|
|
if (subStepSizeCryst <= 0.0_pReal) call IO_error(268)
|
|
|
|
if (stepIncreaseCryst <= 0.0_pReal) call IO_error(268)
|
2009-10-26 22:13:43 +05:30
|
|
|
if (subStepMinHomog <= 0.0_pReal) call IO_error(268)
|
2009-11-10 19:06:27 +05:30
|
|
|
if (subStepSizeHomog <= 0.0_pReal) call IO_error(268)
|
|
|
|
if (stepIncreaseHomog <= 0.0_pReal) call IO_error(268)
|
2009-07-31 17:32:20 +05:30
|
|
|
if (rTol_crystalliteState <= 0.0_pReal) call IO_error(269)
|
2009-08-11 22:01:57 +05:30
|
|
|
if (rTol_crystalliteTemperature <= 0.0_pReal) call IO_error(276) !! oops !!
|
2009-07-31 17:32:20 +05:30
|
|
|
if (rTol_crystalliteStress <= 0.0_pReal) call IO_error(270)
|
|
|
|
if (aTol_crystalliteStress <= 0.0_pReal) call IO_error(271)
|
2011-02-23 18:00:52 +05:30
|
|
|
if (any(numerics_integrator <= 0_pInt) .or. any(numerics_integrator >= 6_pInt)) &
|
2010-10-01 17:48:49 +05:30
|
|
|
call IO_error(298)
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2009-11-17 19:12:38 +05:30
|
|
|
!* RGC parameters: added <<<updated 17.11.2009>>>
|
2009-07-31 17:32:20 +05:30
|
|
|
if (absTol_RGC <= 0.0_pReal) call IO_error(272)
|
|
|
|
if (relTol_RGC <= 0.0_pReal) call IO_error(273)
|
|
|
|
if (absMax_RGC <= 0.0_pReal) call IO_error(274)
|
|
|
|
if (relMax_RGC <= 0.0_pReal) call IO_error(275)
|
2009-08-11 22:01:57 +05:30
|
|
|
if (pPert_RGC <= 0.0_pReal) call IO_error(276) !! oops !!
|
2009-07-31 17:32:20 +05:30
|
|
|
if (xSmoo_RGC <= 0.0_pReal) call IO_error(277)
|
2010-03-24 18:50:12 +05:30
|
|
|
if (viscPower_RGC < 0.0_pReal) call IO_error(278)
|
2009-11-24 20:30:25 +05:30
|
|
|
if (viscModus_RGC < 0.0_pReal) call IO_error(278)
|
2010-03-24 18:50:12 +05:30
|
|
|
if (refRelaxRate_RGC <= 0.0_pReal) call IO_error(278)
|
2009-11-17 19:12:38 +05:30
|
|
|
if (maxdRelax_RGC <= 0.0_pReal) call IO_error(288)
|
2009-12-16 21:50:53 +05:30
|
|
|
if (maxVolDiscr_RGC <= 0.0_pReal) call IO_error(289)
|
|
|
|
if (volDiscrMod_RGC < 0.0_pReal) call IO_error(289)
|
|
|
|
if (volDiscrPow_RGC <= 0.0_pReal) call IO_error(289)
|
2010-10-13 21:34:44 +05:30
|
|
|
|
|
|
|
!* spectral parameters
|
2011-02-21 20:07:38 +05:30
|
|
|
if (err_div_tol <= 0.0_pReal) call IO_error(49)
|
|
|
|
if (err_stress_tolrel <= 0.0_pReal) call IO_error(49)
|
|
|
|
if (itmax <= 1.0_pInt) call IO_error(49)
|
2010-10-13 21:34:44 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
if (fixedSeed <= 0_pInt) then
|
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
write(6,'(a)') 'Random is random!'
|
|
|
|
!$OMP END CRITICAL (write2out)
|
|
|
|
endif
|
2009-06-15 18:41:21 +05:30
|
|
|
endsubroutine
|
|
|
|
|
2009-07-31 17:32:20 +05:30
|
|
|
END MODULE numerics
|