defined locally
This commit is contained in:
parent
c5bd45bf57
commit
dda2f2cf22
|
@ -59,8 +59,8 @@ subroutine discretization_grid_init(restart)
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
j, &
|
j, &
|
||||||
debug_e, &
|
debug_element, &
|
||||||
debug_i
|
debug_ip
|
||||||
integer(C_INTPTR_T) :: &
|
integer(C_INTPTR_T) :: &
|
||||||
devNull, z, z_offset
|
devNull, z, z_offset
|
||||||
|
|
||||||
|
@ -88,8 +88,8 @@ subroutine discretization_grid_init(restart)
|
||||||
|
|
||||||
!-------------------------------------------------------------------------------------------------
|
!-------------------------------------------------------------------------------------------------
|
||||||
! debug parameters
|
! debug parameters
|
||||||
debug_e = debug_root%get_asInt('element',defaultVal=1)
|
debug_element = debug_root%get_asInt('element',defaultVal=1)
|
||||||
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
debug_ip = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! general discretization
|
! general discretization
|
||||||
|
@ -128,8 +128,8 @@ subroutine discretization_grid_init(restart)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! sanity checks for debugging
|
! sanity checks for debugging
|
||||||
if (debug_e < 1 .or. debug_e > product(myGrid)) call IO_error(602,ext_msg='element') ! selected element does not exist
|
if (debug_element < 1 .or. debug_element > product(myGrid)) call IO_error(602,ext_msg='element') ! selected element does not exist
|
||||||
if (debug_i /= 1) call IO_error(602,ext_msg='IP') ! selected IP does not exist
|
if (debug_ip /= 1) call IO_error(602,ext_msg='IP') ! selected IP does not exist
|
||||||
|
|
||||||
end subroutine discretization_grid_init
|
end subroutine discretization_grid_init
|
||||||
|
|
||||||
|
|
|
@ -45,6 +45,8 @@ module grid_mech_FEM
|
||||||
end type tNumerics
|
end type tNumerics
|
||||||
|
|
||||||
type(tNumerics), private :: num
|
type(tNumerics), private :: num
|
||||||
|
logical, private:: &
|
||||||
|
debug_rotation
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! PETSc data
|
! PETSc data
|
||||||
|
@ -115,13 +117,19 @@ subroutine grid_mech_FEM_init
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
fileName
|
fileName
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
num_grid
|
num_grid, &
|
||||||
|
debug_grid
|
||||||
real(pReal), dimension(3,3,3,3) :: devNull
|
real(pReal), dimension(3,3,3,3) :: devNull
|
||||||
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
||||||
u_current,u_lastInc
|
u_current,u_lastInc
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- grid_mech_FEM init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- grid_mech_FEM init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
!-----------------------------------------------------------------------------------------------
|
||||||
|
! debugging options
|
||||||
|
debug_grid => debug_root%get('grid', defaultVal=emptyList)
|
||||||
|
debug_rotation = debug_grid%contains('rotation')
|
||||||
|
|
||||||
!-------------------------------------------------------------------------------------------------
|
!-------------------------------------------------------------------------------------------------
|
||||||
! read numerical parameter and do sanity checks
|
! read numerical parameter and do sanity checks
|
||||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||||
|
@ -499,11 +507,6 @@ subroutine formResidual(da_local,x_local, &
|
||||||
PetscObject :: dummy
|
PetscObject :: dummy
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
real(pReal), dimension(3,3,3,3) :: devNull
|
real(pReal), dimension(3,3,3,3) :: devNull
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_grid ! pointer to grid debug options
|
|
||||||
|
|
||||||
debug_grid => debug_root%get('grid',defaultVal=emptyList)
|
|
||||||
|
|
||||||
|
|
||||||
call SNESGetNumberFunctionEvals(mech_snes,nfuncs,ierr); CHKERRQ(ierr)
|
call SNESGetNumberFunctionEvals(mech_snes,nfuncs,ierr); CHKERRQ(ierr)
|
||||||
call SNESGetIterationNumber(mech_snes,PETScIter,ierr); CHKERRQ(ierr)
|
call SNESGetIterationNumber(mech_snes,PETScIter,ierr); CHKERRQ(ierr)
|
||||||
|
@ -515,7 +518,7 @@ subroutine formResidual(da_local,x_local, &
|
||||||
newIteration: if (totalIter <= PETScIter) then
|
newIteration: if (totalIter <= PETScIter) then
|
||||||
totalIter = totalIter + 1
|
totalIter = totalIter + 1
|
||||||
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter+1, '≤', num%itmax
|
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter+1, '≤', num%itmax
|
||||||
if (debug_grid%contains('rotation')) &
|
if (debug_rotation) &
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
||||||
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
|
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
||||||
|
|
|
@ -44,6 +44,9 @@ module grid_mech_spectral_basic
|
||||||
|
|
||||||
type(tNumerics) :: num ! numerics parameters. Better name?
|
type(tNumerics) :: num ! numerics parameters. Better name?
|
||||||
|
|
||||||
|
logical, private:: &
|
||||||
|
debug_rotation
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! PETSc data
|
! PETSc data
|
||||||
DM :: da
|
DM :: da
|
||||||
|
@ -97,7 +100,8 @@ subroutine grid_mech_spectral_basic_init
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
temp33_Real = 0.0_pReal
|
temp33_Real = 0.0_pReal
|
||||||
class (tNode), pointer :: &
|
class (tNode), pointer :: &
|
||||||
num_grid
|
num_grid, &
|
||||||
|
debug_grid
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
||||||
|
@ -116,6 +120,11 @@ subroutine grid_mech_spectral_basic_init
|
||||||
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
||||||
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
||||||
|
|
||||||
|
!-------------------------------------------------------------------------------------------------
|
||||||
|
! debugging options
|
||||||
|
debug_grid => debug_root%get('grid', defaultVal=emptyList)
|
||||||
|
debug_rotation = debug_grid%contains('rotation')
|
||||||
|
|
||||||
!-------------------------------------------------------------------------------------------------
|
!-------------------------------------------------------------------------------------------------
|
||||||
! read numerical parameters and do sanity checks
|
! read numerical parameters and do sanity checks
|
||||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||||
|
@ -459,11 +468,6 @@ subroutine formResidual(in, F, &
|
||||||
nfuncs
|
nfuncs
|
||||||
PetscObject :: dummy
|
PetscObject :: dummy
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_grid ! pointer to constitutive debug options
|
|
||||||
|
|
||||||
debug_grid => debug_root%get('grid', defaultVal=emptyList)
|
|
||||||
|
|
||||||
|
|
||||||
call SNESGetNumberFunctionEvals(snes,nfuncs,ierr); CHKERRQ(ierr)
|
call SNESGetNumberFunctionEvals(snes,nfuncs,ierr); CHKERRQ(ierr)
|
||||||
call SNESGetIterationNumber(snes,PETScIter,ierr); CHKERRQ(ierr)
|
call SNESGetIterationNumber(snes,PETScIter,ierr); CHKERRQ(ierr)
|
||||||
|
@ -474,7 +478,7 @@ subroutine formResidual(in, F, &
|
||||||
newIteration: if (totalIter <= PETScIter) then
|
newIteration: if (totalIter <= PETScIter) then
|
||||||
totalIter = totalIter + 1
|
totalIter = totalIter + 1
|
||||||
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax
|
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax
|
||||||
if (debug_grid%contains('rotation')) &
|
if (debug%rotation) &
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
||||||
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
|
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
||||||
|
|
|
@ -50,6 +50,8 @@ module grid_mech_spectral_polarisation
|
||||||
|
|
||||||
type(tNumerics) :: num ! numerics parameters. Better name?
|
type(tNumerics) :: num ! numerics parameters. Better name?
|
||||||
|
|
||||||
|
logical, private :: debug_rotation
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! PETSc data
|
! PETSc data
|
||||||
DM :: da
|
DM :: da
|
||||||
|
@ -109,7 +111,8 @@ subroutine grid_mech_spectral_polarisation_init
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
temp33_Real = 0.0_pReal
|
temp33_Real = 0.0_pReal
|
||||||
class (tNode), pointer :: &
|
class (tNode), pointer :: &
|
||||||
num_grid
|
num_grid, &
|
||||||
|
debug_grid
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
||||||
|
@ -127,6 +130,11 @@ subroutine grid_mech_spectral_polarisation_init
|
||||||
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
||||||
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
||||||
|
|
||||||
|
!------------------------------------------------------------------------------------------------
|
||||||
|
! debugging options
|
||||||
|
debug_grid => debug_root%get('grid',defaultVal=emptyList)
|
||||||
|
debug_rotation = debug_grid%contains('rotation')
|
||||||
|
|
||||||
!-------------------------------------------------------------------------------------------------
|
!-------------------------------------------------------------------------------------------------
|
||||||
! read numerical parameters
|
! read numerical parameters
|
||||||
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||||
|
@ -526,12 +534,9 @@ subroutine formResidual(in, FandF_tau, &
|
||||||
nfuncs
|
nfuncs
|
||||||
PetscObject :: dummy
|
PetscObject :: dummy
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
class(tNode), pointer :: &
|
integer :: &
|
||||||
debug_grid ! pointer to grid debug options
|
|
||||||
integer :: &
|
|
||||||
i, j, k, e
|
i, j, k, e
|
||||||
|
|
||||||
debug_grid => debug_root%get('grid',defaultVal=emptyList)
|
|
||||||
|
|
||||||
!---------------------------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -557,7 +562,7 @@ subroutine formResidual(in, FandF_tau, &
|
||||||
newIteration: if (totalIter <= PETScIter) then
|
newIteration: if (totalIter <= PETScIter) then
|
||||||
totalIter = totalIter + 1
|
totalIter = totalIter + 1
|
||||||
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax
|
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax
|
||||||
if(debug_grid%contains('rotation')) &
|
if(debug_rotation) &
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
||||||
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
|
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
|
||||||
|
|
|
@ -69,7 +69,7 @@ subroutine discretization_mesh_init(restart)
|
||||||
integer :: dimPlex, &
|
integer :: dimPlex, &
|
||||||
mesh_Nnodes, & !< total number of nodes in mesh
|
mesh_Nnodes, & !< total number of nodes in mesh
|
||||||
j, l, &
|
j, l, &
|
||||||
debug_e, debug_i
|
debug_element, debug_ip
|
||||||
PetscSF :: sf
|
PetscSF :: sf
|
||||||
DM :: globalMesh
|
DM :: globalMesh
|
||||||
PetscInt :: nFaceSets
|
PetscInt :: nFaceSets
|
||||||
|
@ -93,8 +93,8 @@ subroutine discretization_mesh_init(restart)
|
||||||
|
|
||||||
!---------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------
|
||||||
! read debug parameters
|
! read debug parameters
|
||||||
debug_e = debug_root%get_asInt('element',defaultVal=1)
|
debug_element = debug_root%get_asInt('element',defaultVal=1)
|
||||||
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
debug_ip = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
||||||
|
|
||||||
|
|
||||||
call DMPlexCreateFromFile(PETSC_COMM_WORLD,geometryFile,PETSC_TRUE,globalMesh,ierr)
|
call DMPlexCreateFromFile(PETSC_COMM_WORLD,geometryFile,PETSC_TRUE,globalMesh,ierr)
|
||||||
|
@ -172,8 +172,8 @@ subroutine discretization_mesh_init(restart)
|
||||||
CHKERRQ(ierr)
|
CHKERRQ(ierr)
|
||||||
end do
|
end do
|
||||||
|
|
||||||
if (debug_e < 1 .or. debug_e > mesh_NcpElems) call IO_error(602,ext_msg='element')
|
if (debug_element < 1 .or. debug_element > mesh_NcpElems) call IO_error(602,ext_msg='element')
|
||||||
if (debug_i < 1 .or. debug_i > mesh_maxNips) call IO_error(602,ext_msg='IP')
|
if (debug_ip < 1 .or. debug_ip > mesh_maxNips) call IO_error(602,ext_msg='IP')
|
||||||
|
|
||||||
FEsolving_execElem = [1,mesh_NcpElems] ! parallel loop bounds set to comprise all DAMASK elements
|
FEsolving_execElem = [1,mesh_NcpElems] ! parallel loop bounds set to comprise all DAMASK elements
|
||||||
FEsolving_execIP = [1,mesh_maxNips]
|
FEsolving_execIP = [1,mesh_maxNips]
|
||||||
|
|
Loading…
Reference in New Issue