less global variables
This commit is contained in:
parent
19c44d5e97
commit
5cd2be0569
|
@ -15,6 +15,7 @@ module FEM_utilities
|
||||||
use FEsolving
|
use FEsolving
|
||||||
use homogenization
|
use homogenization
|
||||||
use numerics
|
use numerics
|
||||||
|
use YAML_types
|
||||||
use debug
|
use debug
|
||||||
use math
|
use math
|
||||||
use discretization_mesh
|
use discretization_mesh
|
||||||
|
@ -101,10 +102,17 @@ contains
|
||||||
subroutine utilities_init
|
subroutine utilities_init
|
||||||
|
|
||||||
character(len=pStringLen) :: petsc_optionsOrder
|
character(len=pStringLen) :: petsc_optionsOrder
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
numerics_mesh
|
||||||
|
integer :: structOrder
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- DAMASK_FEM_utilities init -+>>>'
|
write(6,'(/,a)') ' <<<+- DAMASK_FEM_utilities init -+>>>'
|
||||||
|
|
||||||
|
numerics_mesh => numerics_root%get('mesh',defaultVal=emptyDict)
|
||||||
|
structOrder = numerics_mesh%get_asInt('structOrder',defaultVal = 2)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! set debugging parameters
|
! set debugging parameters
|
||||||
debugPETSc = iand(debug_level(debug_SPECTRAL),debug_SPECTRALPETSC) /= 0
|
debugPETSc = iand(debug_level(debug_SPECTRAL),debug_SPECTRALPETSC) /= 0
|
||||||
|
|
|
@ -20,6 +20,7 @@ module discretization_mesh
|
||||||
use FEsolving
|
use FEsolving
|
||||||
use FEM_quadrature
|
use FEM_quadrature
|
||||||
use prec
|
use prec
|
||||||
|
use YAML_types
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
@ -84,6 +85,13 @@ subroutine discretization_mesh_init(restart)
|
||||||
IS :: faceSetIS
|
IS :: faceSetIS
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
|
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
numerics_mesh
|
||||||
|
integer :: integrationOrder
|
||||||
|
|
||||||
|
numerics_mesh => numerics_root%get('mesh',defaultVal=emptyDict)
|
||||||
|
integrationOrder = numerics_mesh%get_asInt('integrationorder',defaultVal = 2)
|
||||||
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- mesh init -+>>>'
|
write(6,'(/,a)') ' <<<+- mesh init -+>>>'
|
||||||
|
|
||||||
|
|
|
@ -19,6 +19,7 @@ module mesh_mech_FEM
|
||||||
use discretization_mesh
|
use discretization_mesh
|
||||||
use DAMASK_interface
|
use DAMASK_interface
|
||||||
use numerics
|
use numerics
|
||||||
|
use YAML_types
|
||||||
use FEM_quadrature
|
use FEM_quadrature
|
||||||
use homogenization
|
use homogenization
|
||||||
use math
|
use math
|
||||||
|
@ -94,8 +95,15 @@ subroutine FEM_mech_init(fieldBC)
|
||||||
character(len=*), parameter :: prefix = 'mechFE_'
|
character(len=*), parameter :: prefix = 'mechFE_'
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
|
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
numerics_mesh
|
||||||
|
integer :: integrationOrder
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- FEM_mech init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- FEM_mech init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
numerics_mesh => numerics_root%get('mesh',defaultVal=emptyDict)
|
||||||
|
integrationOrder = numerics_mesh%get_asInt('integrationorder',defaultVal = 2)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! Setup FEM mech mesh
|
! Setup FEM mech mesh
|
||||||
call DMClone(geomMesh,mech_mesh,ierr); CHKERRQ(ierr)
|
call DMClone(geomMesh,mech_mesh,ierr); CHKERRQ(ierr)
|
||||||
|
@ -321,6 +329,12 @@ subroutine FEM_mech_formResidual(dm_local,xx_local,f_local,dummy,ierr)
|
||||||
PetscInt :: bcSize
|
PetscInt :: bcSize
|
||||||
IS :: bcPoints
|
IS :: bcPoints
|
||||||
|
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
numerics_mesh
|
||||||
|
logical :: BBarStabilisation
|
||||||
|
|
||||||
|
numerics_mesh => numerics_root%get('mesh',defaultVal=emptyDict)
|
||||||
|
BBarStabilisation = numerics_mesh%get_asBool('bbarstabilisation',defaultVal = .false.)
|
||||||
|
|
||||||
allocate(pV0(dimPlex))
|
allocate(pV0(dimPlex))
|
||||||
allocate(pcellJ(dimPlex**2))
|
allocate(pcellJ(dimPlex**2))
|
||||||
|
@ -464,6 +478,12 @@ subroutine FEM_mech_formJacobian(dm_local,xx_local,Jac_pre,Jac,dummy,ierr)
|
||||||
|
|
||||||
IS :: bcPoints
|
IS :: bcPoints
|
||||||
|
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
numerics_mesh
|
||||||
|
logical :: BBarStabilisation
|
||||||
|
|
||||||
|
numerics_mesh => numerics_root%get('mesh',defaultVal=emptyDict)
|
||||||
|
BBarStabilisation = numerics_mesh%get_asBool('bbarstabilisation',defaultVal = .false.)
|
||||||
|
|
||||||
allocate(pV0(dimPlex))
|
allocate(pV0(dimPlex))
|
||||||
allocate(pcellJ(dimPlex**2))
|
allocate(pcellJ(dimPlex**2))
|
||||||
|
@ -647,7 +667,7 @@ subroutine FEM_mech_converged(snes_local,PETScIter,xnorm,snorm,fnorm,reason,dumm
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! report
|
! report
|
||||||
divTol = max(maxval(abs(P_av(1:dimPlex,1:dimPlex)))*err_struct_tolRel,err_struct_tolAbs)
|
divTol = max(maxval(abs(P_av(1:dimPlex,1:dimPlex)))*1.0e-4_pReal,1.0e-10_pReal)
|
||||||
call SNESConvergedDefault(snes_local,PETScIter,xnorm,snorm,fnorm/divTol,reason,dummy,ierr)
|
call SNESConvergedDefault(snes_local,PETScIter,xnorm,snorm,fnorm/divTol,reason,dummy,ierr)
|
||||||
CHKERRQ(ierr)
|
CHKERRQ(ierr)
|
||||||
if (terminallyIll) reason = SNES_DIVERGED_FUNCTION_DOMAIN
|
if (terminallyIll) reason = SNES_DIVERGED_FUNCTION_DOMAIN
|
||||||
|
|
|
@ -35,9 +35,6 @@ module numerics
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! field parameters:
|
! 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
|
|
||||||
integer, protected, public :: &
|
integer, protected, public :: &
|
||||||
itmax = 250, & !< maximum number of iterations
|
itmax = 250, & !< maximum number of iterations
|
||||||
itmin = 1, & !< minimum number of iterations
|
itmin = 1, & !< minimum number of iterations
|
||||||
|
@ -63,11 +60,6 @@ module numerics
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! Mesh parameters:
|
! Mesh parameters:
|
||||||
#ifdef Mesh
|
#ifdef Mesh
|
||||||
integer, protected, public :: &
|
|
||||||
integrationOrder = 2, & !< order of quadrature rule required
|
|
||||||
structOrder = 2 !< order of displacement shape functions
|
|
||||||
logical, protected, public :: &
|
|
||||||
BBarStabilisation = .false.
|
|
||||||
character(len=pStringLen), protected, public :: &
|
character(len=pStringLen), protected, public :: &
|
||||||
petsc_options = ''
|
petsc_options = ''
|
||||||
#endif
|
#endif
|
||||||
|
@ -90,7 +82,6 @@ subroutine numerics_init
|
||||||
key
|
key
|
||||||
class (tNode), pointer :: &
|
class (tNode), pointer :: &
|
||||||
num_grid, &
|
num_grid, &
|
||||||
num_mesh, &
|
|
||||||
num_generic
|
num_generic
|
||||||
logical :: fexist
|
logical :: fexist
|
||||||
!$ character(len=6) DAMASK_NumThreadsString ! environment variable DAMASK_NUM_THREADS
|
!$ character(len=6) DAMASK_NumThreadsString ! environment variable DAMASK_NUM_THREADS
|
||||||
|
@ -181,30 +172,9 @@ subroutine numerics_init
|
||||||
charLength = num_generic%get_asFloat(key)
|
charLength = num_generic%get_asFloat(key)
|
||||||
case ('residualStiffness')
|
case ('residualStiffness')
|
||||||
residualStiffness = num_generic%get_asFloat(key)
|
residualStiffness = num_generic%get_asFloat(key)
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! field parameters
|
|
||||||
case ('err_struct_tolabs')
|
|
||||||
err_struct_tolAbs = num_generic%get_asFloat(key)
|
|
||||||
case ('err_struct_tolrel')
|
|
||||||
err_struct_tolRel = num_generic%get_asFloat(key)
|
|
||||||
endselect
|
endselect
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
#ifdef Mesh
|
|
||||||
num_grid => numerics_root%get('mesh',defaultVal=emptyDict)
|
|
||||||
do i=1,num_grid%length
|
|
||||||
key = num_grid%getKey(i)
|
|
||||||
select case(key)
|
|
||||||
case ('integrationorder')
|
|
||||||
integrationorder = num_generic%get_asInt(key)
|
|
||||||
case ('structorder')
|
|
||||||
structorder = num_generic%get_asInt(key)
|
|
||||||
case ('bbarstabilisation')
|
|
||||||
BBarStabilisation = num_generic%get_asInt(key) > 0
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
#endif
|
|
||||||
|
|
||||||
else fileExists
|
else fileExists
|
||||||
write(6,'(a,/)') ' using standard values'
|
write(6,'(a,/)') ' using standard values'
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -237,8 +207,6 @@ subroutine numerics_init
|
||||||
write(6,'(a24,1x,i8)') ' itmin: ',itmin
|
write(6,'(a24,1x,i8)') ' itmin: ',itmin
|
||||||
write(6,'(a24,1x,i8)') ' maxCutBack: ',maxCutBack
|
write(6,'(a24,1x,i8)') ' maxCutBack: ',maxCutBack
|
||||||
write(6,'(a24,1x,i8)') ' maxStaggeredIter: ',stagItMax
|
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
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! spectral parameters
|
! spectral parameters
|
||||||
|
@ -254,13 +222,6 @@ subroutine numerics_init
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! spectral parameters
|
|
||||||
#ifdef Mesh
|
|
||||||
write(6,'(a24,1x,i8)') ' integrationOrder: ',integrationOrder
|
|
||||||
write(6,'(a24,1x,i8)') ' structOrder: ',structOrder
|
|
||||||
write(6,'(a24,1x,L8)') ' B-Bar stabilisation: ',BBarStabilisation
|
|
||||||
#endif
|
|
||||||
|
|
||||||
#ifdef PETSC
|
#ifdef PETSC
|
||||||
write(6,'(a24,1x,a)') ' PETSc_options: ',trim(petsc_options)
|
write(6,'(a24,1x,a)') ' PETSc_options: ',trim(petsc_options)
|
||||||
#endif
|
#endif
|
||||||
|
@ -275,8 +236,6 @@ subroutine numerics_init
|
||||||
if (itmin > itmax .or. itmin < 1) call IO_error(301,ext_msg='itmin')
|
if (itmin > itmax .or. itmin < 1) call IO_error(301,ext_msg='itmin')
|
||||||
if (maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
|
if (maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
|
||||||
if (stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter')
|
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')
|
|
||||||
#ifdef Grid
|
#ifdef Grid
|
||||||
if (err_stress_tolrel <= 0.0_pReal) call IO_error(301,ext_msg='err_stress_tolRel')
|
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_stress_tolabs <= 0.0_pReal) call IO_error(301,ext_msg='err_stress_tolAbs')
|
||||||
|
|
Loading…
Reference in New Issue