Skip to content

Commit

Permalink
Switch to a nested iteration
Browse files Browse the repository at this point in the history
+ correct some typos
  • Loading branch information
mmalinen committed Nov 5, 2024
1 parent 2e7fa3b commit ced2372
Show file tree
Hide file tree
Showing 4 changed files with 39 additions and 17 deletions.
2 changes: 1 addition & 1 deletion fem/src/CRSMatrix.F90
Original file line number Diff line number Diff line change
Expand Up @@ -399,7 +399,7 @@ END SUBROUTINE CRS_AddToMatrixElement


!------------------------------------------------------------------------------
!> Check existance of a matrix element.
!> Check existence of a matrix element.
!------------------------------------------------------------------------------
FUNCTION CRS_CheckMatrixElement( A,i,j ) RESULT ( Found )
!------------------------------------------------------------------------------
Expand Down
8 changes: 4 additions & 4 deletions fem/src/VankaCreate.F90
Original file line number Diff line number Diff line change
Expand Up @@ -284,7 +284,7 @@ SUBROUTINE VankaCreate(A,Solver)

CASE(0)

! Pick entries related to ene single element and inverse the matrix.
! Pick entries related to a single element and inverse the matrix.
! Add the inverse to the preconditioning matrix.
!-------------------------------------------------------------------
Active = GetNOFActive(Solver)
Expand Down Expand Up @@ -444,13 +444,13 @@ SUBROUTINE VankaCreate(A,Solver)
Mesh => Solver % Mesh
IF( Mesh % MeshDim == 3 ) THEN
IF(.NOT. ASSOCIATED(Mesh % Faces)) THEN
CALL Warn('VankaCreate','This mode requires existance of Faces in 3D!')
CALL Warn('VankaCreate','This mode requires existence of Faces in 3D!')
CALL FindMeshFaces3D(Mesh)
END IF
NoElems = Mesh % NumberOfFaces
ELSE
IF(.NOT. ASSOCIATED(Mesh % Edges)) THEN
CALL Warn('VankaCreate','This mode requires existance of Edges in 2D!')
CALL Warn('VankaCreate','This mode requires existence of Edges in 2D!')
CALL FindMeshEdges2D(Mesh)
END IF

Expand Down Expand Up @@ -604,7 +604,7 @@ SUBROUTINE VankaCreate(A,Solver)
A % ILUCols => B % Cols
A % ILURows => B % Rows

! Nullify these so that they wont be destroyed
! Nullify these so that they won't be destroyed
NULLIFY( B % Values, B % Cols, B % Rows)
CALL FreeMatrix( B )
END IF
Expand Down
2 changes: 1 addition & 1 deletion fem/src/modules/VectorHelmholtz.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1008,7 +1008,7 @@ SUBROUTINE LocalMatrixBC( BC, Element, n, nd, InitHandles )
DO p=1,nd
L(:) = L(:) + CMPLX(Re_Eigenf(n+p) * WBasis(p,:), Im_Eigenf(n+p) * WBasis(p,:), kind=dp)
END DO
L = 2 * B * L
L = 2.0_dp * B * L
END IF
ELSE
MagLoad = ListGetElementComplex3D( MagLoad_h, Basis, Element, Found, GaussPoint = t )
Expand Down
44 changes: 33 additions & 11 deletions fem/tests/EM_port_eigen_3D/port_eigenanalysis_3D.sif
Original file line number Diff line number Diff line change
Expand Up @@ -140,20 +140,42 @@ Solver 3
Eigenfunction Source = Logical True
Variable = EF[EF re:1 EF im:1]

Linear System Symmetric = False
Linear System Scaling = True
Linear System Solver = String "Iterative"
!Linear System Solver = String "Direct"
Linear System Iterative Method = String "bicgstabl"
BiCGstabl polynomial degree = Integer 4

Linear System Block Mode = True
Block Nested System = True
Block Preconditioner = True
Block Scaling = True

Linear System Preconditioning Damp Coefficient = Real 0.0
Linear System Preconditioning Damp Coefficient Im = Real -1.0
Mass-proportional Damping = True
Linear System Preconditioning = String ILU0
! Linear System ILUT Tolerance = Real 3e-3
Linear System Max Iterations = Integer 4000
Linear System Convergence Tolerance = 1.0e-7

! Linear system solver for the outer loop:
!-----------------------------------------
Outer: Linear System Solver = "Iterative"
Outer: Linear System Convergence Tolerance = 1e-7
! Outer: Linear System Normwise Backward Error = True
Outer: Linear System Iterative Method = gcr
Outer: Linear System GCR Restart = 100
Outer: Linear System Residual Output = 1
Outer: Linear System Max Iterations = 100
Outer: Linear System Pseudo Complex = True

! Linear system solver for the inner solution:
!---------------------------------------------
$blocktol = 5.0e-2

block 11: Linear System Solver = "Iterative"
block 11: Linear System Complex = True
block 11: Linear System Row Equilibration = False
block 11: Linear System Preconditioning = ILUT
block 11: Linear System ILUT Tolerance = 3.0e-1
block 11: Linear System Residual Output = 5
block 11: Linear System Max Iterations = 200
block 11: Linear System Iterative Method = GCR
block 11: Linear System GCR Restart = 50
! block 11: BiCGstabl polynomial degree = 4
block 11: Linear System Normwise Backward Error = False
block 11: Linear System Convergence Tolerance = $blocktol

Linear System Abort not Converged = False

Expand Down

0 comments on commit ced2372

Please sign in to comment.