one implicit none is enough
This commit is contained in:
parent
8f58f1348e
commit
d0a4cbf8d5
|
@ -64,7 +64,6 @@ subroutine grid_damage_spectral_init
|
||||||
worldsize, &
|
worldsize, &
|
||||||
petsc_options
|
petsc_options
|
||||||
|
|
||||||
implicit none
|
|
||||||
PetscInt, dimension(worldsize) :: localK
|
PetscInt, dimension(worldsize) :: localK
|
||||||
integer :: i, j, k, cell
|
integer :: i, j, k, cell
|
||||||
DM :: damage_grid
|
DM :: damage_grid
|
||||||
|
@ -164,7 +163,6 @@ function grid_damage_spectral_solution(timeinc,timeinc_old,loadCaseTime) result(
|
||||||
use damage_nonlocal, only: &
|
use damage_nonlocal, only: &
|
||||||
damage_nonlocal_putNonLocalDamage
|
damage_nonlocal_putNonLocalDamage
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), intent(in) :: &
|
real(pReal), intent(in) :: &
|
||||||
timeinc, & !< increment in time for current solution
|
timeinc, & !< increment in time for current solution
|
||||||
timeinc_old, & !< increment in time of last increment
|
timeinc_old, & !< increment in time of last increment
|
||||||
|
@ -236,7 +234,6 @@ subroutine grid_damage_spectral_forward
|
||||||
damage_nonlocal_getDiffusion33, &
|
damage_nonlocal_getDiffusion33, &
|
||||||
damage_nonlocal_getMobility
|
damage_nonlocal_getMobility
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer :: i, j, k, cell
|
integer :: i, j, k, cell
|
||||||
DM :: dm_local
|
DM :: dm_local
|
||||||
PetscScalar, dimension(:,:,:), pointer :: x_scal
|
PetscScalar, dimension(:,:,:), pointer :: x_scal
|
||||||
|
@ -301,7 +298,6 @@ subroutine formResidual(in,x_scal,f_scal,dummy,ierr)
|
||||||
damage_nonlocal_getDiffusion33, &
|
damage_nonlocal_getDiffusion33, &
|
||||||
damage_nonlocal_getMobility
|
damage_nonlocal_getMobility
|
||||||
|
|
||||||
implicit none
|
|
||||||
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: &
|
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: &
|
||||||
in
|
in
|
||||||
PetscScalar, dimension( &
|
PetscScalar, dimension( &
|
||||||
|
|
|
@ -99,7 +99,6 @@ subroutine grid_mech_FEM_init
|
||||||
use math, only: &
|
use math, only: &
|
||||||
math_invSym3333
|
math_invSym3333
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal) :: HGCoeff = 0e-2_pReal
|
real(pReal) :: HGCoeff = 0e-2_pReal
|
||||||
PetscInt, dimension(:), allocatable :: localK
|
PetscInt, dimension(:), allocatable :: localK
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
|
@ -133,9 +132,9 @@ subroutine grid_mech_FEM_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! allocate global fields
|
! allocate global fields
|
||||||
allocate (F (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
allocate(F (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
||||||
allocate (P_current (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
allocate(P_current (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
||||||
allocate (F_lastInc (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
allocate(F_lastInc (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! initialize solver specific parts of PETSc
|
! initialize solver specific parts of PETSc
|
||||||
|
@ -166,8 +165,8 @@ subroutine grid_mech_FEM_init
|
||||||
CHKERRQ(ierr)
|
CHKERRQ(ierr)
|
||||||
call DMSNESSetJacobianLocal(mech_grid,formJacobian,PETSC_NULL_SNES,ierr)
|
call DMSNESSetJacobianLocal(mech_grid,formJacobian,PETSC_NULL_SNES,ierr)
|
||||||
CHKERRQ(ierr)
|
CHKERRQ(ierr)
|
||||||
call SNESSetConvergenceTest(mech_snes,converged,PETSC_NULL_SNES,PETSC_NULL_FUNCTION,ierr)
|
call SNESSetConvergenceTest(mech_snes,converged,PETSC_NULL_SNES,PETSC_NULL_FUNCTION,ierr) ! specify custom convergence check function "_converged"
|
||||||
CHKERRQ(ierr) ! specify custom convergence check function "_converged"
|
CHKERRQ(ierr)
|
||||||
call SNESSetMaxLinearSolveFailures(mech_snes, huge(1), ierr); CHKERRQ(ierr) ! ignore linear solve failures
|
call SNESSetMaxLinearSolveFailures(mech_snes, huge(1), ierr); CHKERRQ(ierr) ! ignore linear solve failures
|
||||||
call SNESSetFromOptions(mech_snes,ierr); CHKERRQ(ierr) ! pull it all together with additional cli arguments
|
call SNESSetFromOptions(mech_snes,ierr); CHKERRQ(ierr) ! pull it all together with additional cli arguments
|
||||||
|
|
||||||
|
@ -253,7 +252,6 @@ function grid_mech_FEM_solution(incInfoIn,timeinc,timeinc_old,stress_BC,rotation
|
||||||
restartWrite, &
|
restartWrite, &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! input data for solution
|
! input data for solution
|
||||||
character(len=*), intent(in) :: &
|
character(len=*), intent(in) :: &
|
||||||
|
@ -326,7 +324,6 @@ subroutine grid_mech_FEM_forward(guess,timeinc,timeinc_old,loadCaseTime,deformat
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
restartWrite
|
restartWrite
|
||||||
|
|
||||||
implicit none
|
|
||||||
logical, intent(in) :: &
|
logical, intent(in) :: &
|
||||||
guess
|
guess
|
||||||
real(pReal), intent(in) :: &
|
real(pReal), intent(in) :: &
|
||||||
|
@ -352,7 +349,7 @@ subroutine grid_mech_FEM_forward(guess,timeinc,timeinc_old,loadCaseTime,deformat
|
||||||
else
|
else
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! restart information for spectral solver
|
! restart information for spectral solver
|
||||||
if (restartWrite) then ! QUESTION: where is this logical properly set?
|
if (restartWrite) then
|
||||||
write(6,'(/,a)') ' writing converged results for restart';flush(6)
|
write(6,'(/,a)') ' writing converged results for restart';flush(6)
|
||||||
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
write(rankStr,'(a1,i0)')'_',worldrank
|
||||||
|
@ -424,7 +421,7 @@ end subroutine grid_mech_FEM_forward
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief convergence check
|
!> @brief convergence check
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine converged(snes_local,PETScIter,devNull1,devNull2,devNull3,reason,dummy,ierr)
|
subroutine converged(snes_local,PETScIter,devNull1,devNull2,fnorm,reason,dummy,ierr)
|
||||||
use mesh
|
use mesh
|
||||||
use spectral_utilities
|
use spectral_utilities
|
||||||
use numerics, only: &
|
use numerics, only: &
|
||||||
|
@ -437,13 +434,12 @@ subroutine converged(snes_local,PETScIter,devNull1,devNull2,devNull3,reason,dumm
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
SNES :: snes_local
|
SNES :: snes_local
|
||||||
PetscInt, intent(in) :: PETScIter
|
PetscInt, intent(in) :: PETScIter
|
||||||
PetscReal, intent(in) :: &
|
PetscReal, intent(in) :: &
|
||||||
devNull1, &
|
devNull1, &
|
||||||
devNull2, &
|
devNull2, &
|
||||||
devNull3
|
fnorm
|
||||||
SNESConvergedReason :: reason
|
SNESConvergedReason :: reason
|
||||||
PetscObject :: dummy
|
PetscObject :: dummy
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
|
@ -508,7 +504,6 @@ subroutine formResidual(da_local,x_local, &
|
||||||
use homogenization, only: &
|
use homogenization, only: &
|
||||||
materialpoint_dPdF
|
materialpoint_dPdF
|
||||||
|
|
||||||
implicit none
|
|
||||||
DM :: da_local
|
DM :: da_local
|
||||||
Vec :: x_local, f_local
|
Vec :: x_local, f_local
|
||||||
PetscScalar, pointer,dimension(:,:,:,:) :: x_scal, f_scal
|
PetscScalar, pointer,dimension(:,:,:,:) :: x_scal, f_scal
|
||||||
|
@ -627,7 +622,6 @@ subroutine formJacobian(da_local,x_local,Jac_pre,Jac,dummy,ierr)
|
||||||
use homogenization, only: &
|
use homogenization, only: &
|
||||||
materialpoint_dPdF
|
materialpoint_dPdF
|
||||||
|
|
||||||
implicit none
|
|
||||||
|
|
||||||
DM :: da_local
|
DM :: da_local
|
||||||
Vec :: x_local, coordinates
|
Vec :: x_local, coordinates
|
||||||
|
|
|
@ -107,7 +107,6 @@ subroutine grid_mech_spectral_basic_init
|
||||||
use math, only: &
|
use math, only: &
|
||||||
math_invSym3333
|
math_invSym3333
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
temp33_Real = 0.0_pReal
|
temp33_Real = 0.0_pReal
|
||||||
|
@ -221,7 +220,6 @@ function grid_mech_spectral_basic_solution(incInfoIn,timeinc,timeinc_old,stress_
|
||||||
restartWrite, &
|
restartWrite, &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! input data for solution
|
! input data for solution
|
||||||
character(len=*), intent(in) :: &
|
character(len=*), intent(in) :: &
|
||||||
|
@ -298,7 +296,6 @@ subroutine grid_mech_spectral_basic_forward(guess,timeinc,timeinc_old,loadCaseTi
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
restartWrite
|
restartWrite
|
||||||
|
|
||||||
implicit none
|
|
||||||
logical, intent(in) :: &
|
logical, intent(in) :: &
|
||||||
guess
|
guess
|
||||||
real(pReal), intent(in) :: &
|
real(pReal), intent(in) :: &
|
||||||
|
@ -397,7 +394,6 @@ subroutine converged(snes_local,PETScIter,devNull1,devNull2,devNull3,reason,dumm
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
SNES :: snes_local
|
SNES :: snes_local
|
||||||
PetscInt, intent(in) :: PETScIter
|
PetscInt, intent(in) :: PETScIter
|
||||||
PetscReal, intent(in) :: &
|
PetscReal, intent(in) :: &
|
||||||
|
@ -468,7 +464,6 @@ subroutine formResidual(in, F, &
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: in !< DMDA info (needs to be named "in" for macros like XRANGE to work)
|
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: in !< DMDA info (needs to be named "in" for macros like XRANGE to work)
|
||||||
PetscScalar, dimension(3,3,XG_RANGE,YG_RANGE,ZG_RANGE), &
|
PetscScalar, dimension(3,3,XG_RANGE,YG_RANGE,ZG_RANGE), &
|
||||||
intent(in) :: F !< deformation gradient field
|
intent(in) :: F !< deformation gradient field
|
||||||
|
|
|
@ -113,7 +113,6 @@ subroutine grid_mech_spectral_polarisation_init
|
||||||
use math, only: &
|
use math, only: &
|
||||||
math_invSym3333
|
math_invSym3333
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
temp33_Real = 0.0_pReal
|
temp33_Real = 0.0_pReal
|
||||||
|
@ -238,7 +237,6 @@ function grid_mech_spectral_polarisation_solution(incInfoIn,timeinc,timeinc_old,
|
||||||
restartWrite, &
|
restartWrite, &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! input data for solution
|
! input data for solution
|
||||||
character(len=*), intent(in) :: &
|
character(len=*), intent(in) :: &
|
||||||
|
@ -445,7 +443,6 @@ subroutine converged(snes_local,PETScIter,devNull1,devNull2,devNull3,reason,dumm
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
SNES :: snes_local
|
SNES :: snes_local
|
||||||
PetscInt, intent(in) :: PETScIter
|
PetscInt, intent(in) :: PETScIter
|
||||||
PetscReal, intent(in) :: &
|
PetscReal, intent(in) :: &
|
||||||
|
@ -529,7 +526,6 @@ subroutine formResidual(in, FandF_tau, &
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
terminallyIll
|
terminallyIll
|
||||||
|
|
||||||
implicit none
|
|
||||||
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: in !< DMDA info (needs to be named "in" for macros like XRANGE to work)
|
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: in !< DMDA info (needs to be named "in" for macros like XRANGE to work)
|
||||||
PetscScalar, dimension(3,3,2,XG_RANGE,YG_RANGE,ZG_RANGE), &
|
PetscScalar, dimension(3,3,2,XG_RANGE,YG_RANGE,ZG_RANGE), &
|
||||||
target, intent(in) :: FandF_tau
|
target, intent(in) :: FandF_tau
|
||||||
|
|
|
@ -69,7 +69,6 @@ subroutine grid_thermal_spectral_init
|
||||||
worldsize, &
|
worldsize, &
|
||||||
petsc_options
|
petsc_options
|
||||||
|
|
||||||
implicit none
|
|
||||||
PetscInt, dimension(worldsize) :: localK
|
PetscInt, dimension(worldsize) :: localK
|
||||||
integer :: i, j, k, cell
|
integer :: i, j, k, cell
|
||||||
DM :: thermal_grid
|
DM :: thermal_grid
|
||||||
|
@ -167,7 +166,6 @@ function grid_thermal_spectral_solution(timeinc,timeinc_old,loadCaseTime) result
|
||||||
use thermal_conduction, only: &
|
use thermal_conduction, only: &
|
||||||
thermal_conduction_putTemperatureAndItsRate
|
thermal_conduction_putTemperatureAndItsRate
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), intent(in) :: &
|
real(pReal), intent(in) :: &
|
||||||
timeinc, & !< increment in time for current solution
|
timeinc, & !< increment in time for current solution
|
||||||
timeinc_old, & !< increment in time of last increment
|
timeinc_old, & !< increment in time of last increment
|
||||||
|
@ -242,7 +240,6 @@ subroutine grid_thermal_spectral_forward
|
||||||
thermal_conduction_getMassDensity, &
|
thermal_conduction_getMassDensity, &
|
||||||
thermal_conduction_getSpecificHeat
|
thermal_conduction_getSpecificHeat
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer :: i, j, k, cell
|
integer :: i, j, k, cell
|
||||||
DM :: dm_local
|
DM :: dm_local
|
||||||
PetscScalar, dimension(:,:,:), pointer :: x_scal
|
PetscScalar, dimension(:,:,:), pointer :: x_scal
|
||||||
|
@ -311,7 +308,6 @@ subroutine formResidual(in,x_scal,f_scal,dummy,ierr)
|
||||||
thermal_conduction_getMassDensity, &
|
thermal_conduction_getMassDensity, &
|
||||||
thermal_conduction_getSpecificHeat
|
thermal_conduction_getSpecificHeat
|
||||||
|
|
||||||
implicit none
|
|
||||||
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: &
|
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: &
|
||||||
in
|
in
|
||||||
PetscScalar, dimension( &
|
PetscScalar, dimension( &
|
||||||
|
|
Loading…
Reference in New Issue