polishing
This commit is contained in:
parent
fd8994786e
commit
0b2d62e98d
|
@ -73,13 +73,9 @@ program DAMASK_grid
|
|||
character(len=pStringLen) :: &
|
||||
incInfo, &
|
||||
loadcase_string
|
||||
type :: tNumerics
|
||||
integer :: &
|
||||
maxCutBack, & !< max number of cut backs
|
||||
stagItMax !< max number of field level staggered iterations
|
||||
end type tNumerics
|
||||
|
||||
type(tNumerics) :: num
|
||||
integer :: &
|
||||
maxCutBack, & !< max number of cut backs
|
||||
stagItMax !< max number of field level staggered iterations
|
||||
type(tLoadCase), allocatable, dimension(:) :: loadCases !< array of all load cases
|
||||
type(tLoadCase) :: newLoadCase
|
||||
type(tSolutionState), allocatable, dimension(:) :: solres
|
||||
|
@ -119,11 +115,11 @@ program DAMASK_grid
|
|||
!-------------------------------------------------------------------------------------------------
|
||||
! reading field paramters from numerics file and do sanity checks
|
||||
num_grid => numerics_root%get('grid', defaultVal=emptyDict)
|
||||
num%stagItMax = num_grid%get_asInt('maxStaggeredIter',defaultVal=10)
|
||||
num%maxCutBack = num_grid%get_asInt('maxCutBack',defaultVal=3)
|
||||
stagItMax = num_grid%get_asInt('maxStaggeredIter',defaultVal=10)
|
||||
maxCutBack = num_grid%get_asInt('maxCutBack',defaultVal=3)
|
||||
|
||||
if (num%stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter')
|
||||
if (num%maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
|
||||
if (stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter')
|
||||
if (maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! assign mechanics solver depending on selected type
|
||||
|
@ -453,7 +449,7 @@ program DAMASK_grid
|
|||
|
||||
enddo
|
||||
stagIter = stagIter + 1
|
||||
stagIterate = stagIter < num%stagItMax &
|
||||
stagIterate = stagIter < stagItMax &
|
||||
.and. all(solres(:)%converged) &
|
||||
.and. .not. all(solres(:)%stagConverged) ! stationary with respect to staggered iteration
|
||||
enddo
|
||||
|
@ -472,7 +468,7 @@ program DAMASK_grid
|
|||
solres%converged, solres%iterationsNeeded
|
||||
flush(statUnit)
|
||||
endif
|
||||
elseif (cutBackLevel < num%maxCutBack) then ! further cutbacking tolerated?
|
||||
elseif (cutBackLevel < maxCutBack) then ! further cutbacking tolerated?
|
||||
cutBack = .true.
|
||||
stepFraction = (stepFraction - 1) * subStepFactor ! adjust to new denominator
|
||||
cutBackLevel = cutBackLevel + 1
|
||||
|
|
|
@ -28,8 +28,6 @@ module grid_damage_spectral
|
|||
residualStiffness, & !< non-zero residual damage
|
||||
eps_damage_atol, & !< absolute tolerance for damage evolution
|
||||
eps_damage_rtol !< relative tolerance for damage evolution
|
||||
character(len=:), allocatable :: &
|
||||
petsc_options
|
||||
end type tNumerics
|
||||
|
||||
type(tNumerics), private :: num
|
||||
|
@ -86,7 +84,6 @@ subroutine grid_damage_spectral_init
|
|||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameters and do sanity checks
|
||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||
num%petsc_options = num_grid%get_asString('petsc_options',defaultVal='')
|
||||
num%itmax = num_grid%get_asInt ('itmax',defaultVal=250)
|
||||
num%eps_damage_atol = num_grid%get_asFloat ('eps_damage_atol',defaultVal=1.0e-2_pReal)
|
||||
num%eps_damage_rtol = num_grid%get_asFloat ('eps_damage_rtol',defaultVal=1.0e-6_pReal)
|
||||
|
@ -104,7 +101,7 @@ subroutine grid_damage_spectral_init
|
|||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,'-damage_snes_type newtonls -damage_snes_mf &
|
||||
&-damage_snes_ksp_ew -damage_ksp_type fgmres',ierr)
|
||||
CHKERRQ(ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num%petsc_options,ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num_grid%get_asString('petsc_options',defaultVal=''),ierr)
|
||||
CHKERRQ(ierr)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -42,8 +42,6 @@ module grid_mech_FEM
|
|||
eps_div_rtol, & !< relative tolerance for equilibrium
|
||||
eps_stress_atol, & !< absolute tolerance for fullfillment of stress BC
|
||||
eps_stress_rtol !< relative tolerance for fullfillment of stress BC
|
||||
character(len=:), allocatable :: &
|
||||
petsc_options
|
||||
end type tNumerics
|
||||
|
||||
type(tNumerics), private :: num
|
||||
|
@ -127,7 +125,6 @@ subroutine grid_mech_FEM_init
|
|||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameter and do sanity checks
|
||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||
num%petsc_options = num_grid%get_asString('petsc_options', defaultVal='')
|
||||
num%eps_div_atol = num_grid%get_asFloat ('eps_div_atol', defaultVal=1.0e-4_pReal)
|
||||
num%eps_div_rtol = num_grid%get_asFloat ('eps_div_rtol', defaultVal=5.0e-4_pReal)
|
||||
num%eps_stress_atol = num_grid%get_asFloat ('eps_stress_atol', defaultVal=1.0e3_pReal)
|
||||
|
@ -148,7 +145,7 @@ subroutine grid_mech_FEM_init
|
|||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,'-mech_snes_type newtonls -mech_ksp_type fgmres &
|
||||
&-mech_ksp_max_it 25 -mech_pc_type ml -mech_mg_levels_ksp_type chebyshev',ierr)
|
||||
CHKERRQ(ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num%petsc_options,ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num_grid%get_asString('petsc_options',defaultVal=''),ierr)
|
||||
CHKERRQ(ierr)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -40,8 +40,6 @@ module grid_mech_spectral_basic
|
|||
eps_div_rtol, & !< relative tolerance for equilibrium
|
||||
eps_stress_atol, & !< absolute tolerance for fullfillment of stress BC
|
||||
eps_stress_rtol !< relative tolerance for fullfillment of stress BC
|
||||
character(len=:), allocatable :: &
|
||||
petsc_options
|
||||
end type tNumerics
|
||||
|
||||
type(tNumerics) :: num ! numerics parameters. Better name?
|
||||
|
@ -122,7 +120,6 @@ subroutine grid_mech_spectral_basic_init
|
|||
! read numerical parameters and do sanity checks
|
||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||
|
||||
num%petsc_options = num_grid%get_asString ('petsc_options', defaultVal='')
|
||||
num%update_gamma = num_grid%get_asBool ('update_gamma', defaultVal=.false.)
|
||||
num%eps_div_atol = num_grid%get_asFloat ('eps_div_atol', defaultVal=1.0e-4_pReal)
|
||||
num%eps_div_rtol = num_grid%get_asFloat ('eps_div_rtol', defaultVal=5.0e-4_pReal)
|
||||
|
@ -143,7 +140,7 @@ subroutine grid_mech_spectral_basic_init
|
|||
! set default and user defined options for PETSc
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,'-mech_snes_type ngmres',ierr)
|
||||
CHKERRQ(ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num%petsc_options,ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num_grid%get_asString('petsc_options',defaultVal=''),ierr)
|
||||
CHKERRQ(ierr)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -33,8 +33,6 @@ module grid_mech_spectral_polarisation
|
|||
|
||||
type :: tNumerics
|
||||
logical :: update_gamma !< update gamma operator with current stiffness
|
||||
character(len=:), allocatable :: &
|
||||
petsc_options
|
||||
integer :: &
|
||||
itmin, & !< minimum number of iterations
|
||||
itmax !< maximum number of iterations
|
||||
|
@ -133,7 +131,6 @@ subroutine grid_mech_spectral_polarisation_init
|
|||
! read numerical parameters
|
||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||
|
||||
num%petsc_options = num_grid%get_asString('petsc_options', defaultVal='')
|
||||
num%update_gamma = num_grid%get_asBool ('update_gamma', defaultVal=.false.)
|
||||
num%eps_div_atol = num_grid%get_asFloat ('eps_div_atol', defaultVal=1.0e-4_pReal)
|
||||
num%eps_div_rtol = num_grid%get_asFloat ('eps_div_rtol', defaultVal=5.0e-4_pReal)
|
||||
|
@ -161,7 +158,7 @@ subroutine grid_mech_spectral_polarisation_init
|
|||
! set default and user defined options for PETSc
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,'-mech_snes_type ngmres',ierr)
|
||||
CHKERRQ(ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num%petsc_options,ierr)
|
||||
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num_grid%get_asString('petsc_options',defaultVal=''),ierr)
|
||||
CHKERRQ(ierr)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -27,11 +27,11 @@ module grid_thermal_spectral
|
|||
type(tSolutionParams) :: params
|
||||
|
||||
type :: tNumerics
|
||||
integer :: &
|
||||
itmax !< maximum number of iterations
|
||||
real(pReal) :: &
|
||||
eps_thermal_atol, & !< absolute tolerance for thermal equilibrium
|
||||
eps_thermal_rtol !< relative tolerance for thermal equilibrium
|
||||
character(len=:), allocatable :: &
|
||||
petsc_options
|
||||
end type tNumerics
|
||||
|
||||
type(tNumerics) :: num
|
||||
|
@ -81,10 +81,11 @@ subroutine grid_thermal_spectral_init
|
|||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameter and do sanity checks
|
||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||
num%petsc_options = num_grid%get_asString('petsc_options',defaultVal='')
|
||||
num%itmax = num_grid%get_asInt ('itmax', defaultVal=250)
|
||||
num%eps_thermal_atol = num_grid%get_asFloat ('eps_thermal_atol',defaultVal=1.0e-2_pReal)
|
||||
num%eps_thermal_rtol = num_grid%get_asFloat ('eps_thermal_rtol',defaultVal=1.0e-6_pReal)
|
||||
|
||||
if (num%itmax <= 1) call IO_error(301,ext_msg='itmax')
|
||||
if (num%eps_thermal_atol <= 0.0_pReal) call IO_error(301,ext_msg='eps_thermal_atol')
|
||||
if (num%eps_thermal_rtol <= 0.0_pReal) call IO_error(301,ext_msg='eps_thermal_rtol')
|
||||
|
||||
|
@ -155,8 +156,7 @@ function grid_thermal_spectral_solution(timeinc,timeinc_old) result(solution)
|
|||
real(pReal), intent(in) :: &
|
||||
timeinc, & !< increment in time for current solution
|
||||
timeinc_old !< increment in time of last increment
|
||||
integer :: i, j, k, cell, &
|
||||
itmax !< maximum number of iterations
|
||||
integer :: i, j, k, cell
|
||||
type(tSolutionState) :: solution
|
||||
class(tNode), pointer :: &
|
||||
num_grid
|
||||
|
@ -166,12 +166,6 @@ function grid_thermal_spectral_solution(timeinc,timeinc_old) result(solution)
|
|||
PetscErrorCode :: ierr
|
||||
SNESConvergedReason :: reason
|
||||
|
||||
!-------------------------------------------------------------------
|
||||
! reading numerical parameter and do sanity check !TODO: MD: Not Here
|
||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||
itmax = num_grid%get_asInt('itmax',defaultVal=250)
|
||||
if (itmax <= 1) call IO_error(301,ext_msg='itmax')
|
||||
|
||||
solution%converged =.false.
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -184,7 +178,7 @@ function grid_thermal_spectral_solution(timeinc,timeinc_old) result(solution)
|
|||
|
||||
if (reason < 1) then
|
||||
solution%converged = .false.
|
||||
solution%iterationsNeeded = itmax
|
||||
solution%iterationsNeeded = num%itmax
|
||||
else
|
||||
solution%converged = .true.
|
||||
solution%iterationsNeeded = totalIter
|
||||
|
|
|
@ -120,8 +120,7 @@ module spectral_utilities
|
|||
memory_efficient !< calculate gamma operator on the fly
|
||||
character(len=:), allocatable :: &
|
||||
spectral_derivative, & !< approximation used for derivatives in Fourier space
|
||||
FFTW_plan_mode, & !< FFTW plan mode, see www.fftw.org
|
||||
petsc_options
|
||||
FFTW_plan_mode !< FFTW plan mode, see www.fftw.org
|
||||
end type tNumerics
|
||||
|
||||
type(tNumerics), private :: num ! numerics parameters. Better name?
|
||||
|
@ -215,7 +214,7 @@ subroutine spectral_utilities_init
|
|||
if(debugPETSc) write(6,'(3(/,a),/)') &
|
||||
' Initializing PETSc with debug options: ', &
|
||||
trim(PETScDebug), &
|
||||
' add more using the PETSc_Options keyword in numerics.config '; flush(6)
|
||||
' add more using the PETSc_Options keyword in numerics.yaml '; flush(6)
|
||||
|
||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||
|
||||
|
|
18
src/math.f90
18
src/math.f90
|
@ -72,20 +72,11 @@ module math
|
|||
3,2, &
|
||||
3,3 &
|
||||
],shape(MAPPLAIN)) !< arrangement in Plain notation
|
||||
|
||||
type, private :: tNumerics
|
||||
integer :: &
|
||||
randomSeed !< fixed seeding for pseudo-random number generator, Default 0: use random seed
|
||||
|
||||
end type
|
||||
|
||||
type(tNumerics), private :: num
|
||||
|
||||
interface math_eye
|
||||
module procedure math_identity2nd
|
||||
end interface math_eye
|
||||
|
||||
! ToDo: Since random seed is needed only once, I would simplify here
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
private :: &
|
||||
selfTest
|
||||
|
@ -99,7 +90,8 @@ subroutine math_init
|
|||
|
||||
real(pReal), dimension(4) :: randTest
|
||||
integer :: &
|
||||
randSize
|
||||
randSize, &
|
||||
randomSeed !< fixed seeding for pseudo-random number generator, Default 0: use random seed
|
||||
integer, dimension(:), allocatable :: randInit
|
||||
class(tNode), pointer :: &
|
||||
num_generic
|
||||
|
@ -107,12 +99,12 @@ subroutine math_init
|
|||
write(6,'(/,a)') ' <<<+- math init -+>>>'; flush(6)
|
||||
|
||||
num_generic => numerics_root%get('generic',defaultVal=emptyDict)
|
||||
num%randomSeed = num_generic%get_asInt('random_seed', defaultVal = 0)
|
||||
randomSeed = num_generic%get_asInt('random_seed', defaultVal = 0)
|
||||
|
||||
call random_seed(size=randSize)
|
||||
allocate(randInit(randSize))
|
||||
if (num%randomSeed > 0) then
|
||||
randInit = num%randomSeed
|
||||
if (randomSeed > 0) then
|
||||
randInit = randomSeed
|
||||
else
|
||||
call random_seed()
|
||||
call random_seed(get = randInit)
|
||||
|
|
|
@ -63,13 +63,9 @@ program DAMASK_mesh
|
|||
character(len=pStringLen) :: &
|
||||
incInfo, &
|
||||
loadcase_string
|
||||
type :: tNumerics
|
||||
integer :: &
|
||||
stagItMax, & !< max number of field level staggered iterations
|
||||
maxCutBack !< max number of cutbacks
|
||||
end type tNumerics
|
||||
|
||||
type(tNumerics) :: num
|
||||
integer :: &
|
||||
stagItMax, & !< max number of field level staggered iterations
|
||||
maxCutBack !< max number of cutbacks
|
||||
|
||||
type(tLoadCase), allocatable, dimension(:) :: loadCases !< array of all load cases
|
||||
type(tSolutionState), allocatable, dimension(:) :: solres
|
||||
|
@ -87,11 +83,11 @@ program DAMASK_mesh
|
|||
!---------------------------------------------------------------------
|
||||
! reading field information from numerics file and do sanity checks
|
||||
num_mesh => numerics_root%get('mesh', defaultVal=emptyDict)
|
||||
num%stagItMax = num_mesh%get_asInt('maxStaggeredIter',defaultVal=10)
|
||||
num%maxCutBack = num_mesh%get_asInt('maxCutBack',defaultVal=3)
|
||||
stagItMax = num_mesh%get_asInt('maxStaggeredIter',defaultVal=10)
|
||||
maxCutBack = num_mesh%get_asInt('maxCutBack',defaultVal=3)
|
||||
|
||||
if (num%stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter')
|
||||
if (num%maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
|
||||
if (stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter')
|
||||
if (maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
|
||||
|
||||
! reading basic information from load case file and allocate data structure containing load cases
|
||||
call DMGetDimension(geomMesh,dimPlex,ierr); CHKERRA(ierr) !< dimension of mesh (2D or 3D)
|
||||
|
@ -333,7 +329,7 @@ program DAMASK_mesh
|
|||
|
||||
enddo
|
||||
stagIter = stagIter + 1
|
||||
stagIterate = stagIter < num%stagItMax &
|
||||
stagIterate = stagIter < stagItMax &
|
||||
.and. all(solres(:)%converged) &
|
||||
.and. .not. all(solres(:)%stagConverged) ! stationary with respect to staggered iteration
|
||||
enddo
|
||||
|
@ -341,7 +337,7 @@ program DAMASK_mesh
|
|||
! check solution
|
||||
cutBack = .False.
|
||||
if(.not. all(solres(:)%converged .and. solres(:)%stagConverged)) then ! no solution found
|
||||
if (cutBackLevel < num%maxCutBack) then ! do cut back
|
||||
if (cutBackLevel < maxCutBack) then ! do cut back
|
||||
write(6,'(/,a)') ' cut back detected'
|
||||
cutBack = .True.
|
||||
stepFraction = (stepFraction - 1) * subStepFactor ! adjust to new denominator
|
||||
|
|
|
@ -106,15 +106,12 @@ subroutine FEM_utilities_init
|
|||
class(tNode), pointer :: &
|
||||
num_mesh
|
||||
integer :: structOrder !< order of displacement shape functions
|
||||
character(len=:), allocatable :: &
|
||||
petsc_options
|
||||
PetscErrorCode :: ierr
|
||||
|
||||
write(6,'(/,a)') ' <<<+- DAMASK_FEM_utilities init -+>>>'
|
||||
|
||||
num_mesh => numerics_root%get('mesh',defaultVal=emptyDict)
|
||||
structOrder = num_mesh%get_asInt ('structOrder', defaultVal = 2)
|
||||
petsc_options = num_mesh%get_asString('petsc_options', defaultVal='')
|
||||
structOrder = num_mesh%get_asInt('structOrder', defaultVal = 2)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! set debugging parameters
|
||||
|
@ -122,7 +119,7 @@ subroutine FEM_utilities_init
|
|||
if(debugPETSc) write(6,'(3(/,a),/)') &
|
||||
' Initializing PETSc with debug options: ', &
|
||||
trim(PETScDebug), &
|
||||
' add more using the PETSc_Options keyword in numerics.config '
|
||||
' add more using the PETSc_Options keyword in numerics.yaml '
|
||||
flush(6)
|
||||
call PetscOptionsClear(PETSC_NULL_OPTIONS,ierr)
|
||||
CHKERRQ(ierr)
|
||||
|
@ -135,7 +132,7 @@ subroutine FEM_utilities_init
|
|||
&-mech_pc_type ml -mech_mg_levels_ksp_type chebyshev &
|
||||
&-mech_mg_levels_pc_type sor -mech_pc_ml_nullspace user',ierr)
|
||||
CHKERRQ(ierr)
|
||||
call PetscOptionsInsertString(PETSC_NULL_OPTIONS,petsc_options,ierr)
|
||||
call PetscOptionsInsertString(PETSC_NULL_OPTIONS,num_mesh%get_asString('petsc_options',defaultVal=''),ierr)
|
||||
CHKERRQ(ierr)
|
||||
write(petsc_optionsOrder,'(a,i0)') '-mechFE_petscspace_degree ', structOrder
|
||||
call PetscOptionsInsertString(PETSC_NULL_OPTIONS,trim(petsc_optionsOrder),ierr)
|
||||
|
|
Loading…
Reference in New Issue