Skip to content

Commit

Permalink
fixed issue with Solver not being passed as a poitner to FinishAssemb…
Browse files Browse the repository at this point in the history
…ly (SolverUtils.F90)
  • Loading branch information
tzwinger committed Sep 27, 2024
1 parent c290533 commit 044b15d
Show file tree
Hide file tree
Showing 8 changed files with 32 additions and 23 deletions.
7 changes: 4 additions & 3 deletions elmerice/Solvers/Adjoint/Adjoint_LinearSolver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -63,14 +63,14 @@ SUBROUTINE Adjoint_LinearSolver( Model,Solver,dt,TransientSimulation )
USE DefUtils
IMPLICIT NONE
!------------------------------------------------------------------------------
TYPE(Solver_t) :: Solver
TYPE(Solver_t), TARGET :: Solver
TYPE(Model_t) :: Model
REAL(KIND=dp) :: dt
LOGICAL :: TransientSimulation
!------------------------------------------------------------------------------
! Local variables
!------------------------------------------------------------------------------
TYPE(Solver_t),Pointer :: DSolver ! Pointer to the Direct Solver
TYPE(Solver_t),POINTER :: DSolver, PSolver ! Pointer to the Direct Solver and to adjoint solver
TYPE(Variable_t), POINTER :: Sol ! Solution Variable
INTEGER :: DOFs

Expand Down Expand Up @@ -253,7 +253,8 @@ SUBROUTINE Adjoint_LinearSolver( Model,Solver,dt,TransientSimulation )
End Do
EndDo

CALL FinishAssembly( Solver, ForceVector )
PSolver => Solver
CALL FinishAssembly( PSolver, ForceVector )

Unorm = DefaultSolve()

Expand Down
7 changes: 4 additions & 3 deletions elmerice/Solvers/AdjointSSA/AdjointSSA_AdjointSolver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -63,14 +63,14 @@ SUBROUTINE AdjointSSA_AdjointSolver( Model,Solver,dt,TransientSimulation )
USE DefUtils
IMPLICIT NONE
!------------------------------------------------------------------------------
TYPE(Solver_t) :: Solver
TYPE(Solver_t), TARGET :: Solver
TYPE(Model_t) :: Model
REAL(KIND=dp) :: dt
LOGICAL :: TransientSimulation
!------------------------------------------------------------------------------
! Local variables
!------------------------------------------------------------------------------
TYPE(Solver_t),Pointer :: NSSolver
TYPE(Solver_t),POINTER :: NSSolver, PSolver
TYPE(Matrix_t),POINTER :: InitMat,TransMat,StiffMatrix
TYPE(ValueList_t),POINTER :: BC,BF,SolverParams
TYPE(ValueListEntry_t),POINTER :: NormalTangential,NormalTangentialC
Expand Down Expand Up @@ -258,7 +258,8 @@ SUBROUTINE AdjointSSA_AdjointSolver( Model,Solver,dt,TransientSimulation )
End Do
EndDo

CALL FinishAssembly( Solver, ForceVector )
PSolver => Solver
CALL FinishAssembly( PSolver, ForceVector )

Unorm = DefaultSolve()

Expand Down
7 changes: 4 additions & 3 deletions elmerice/Solvers/AdjointSolver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ SUBROUTINE AdjointSolver( Model,Solver,dt,TransientSimulation )

IMPLICIT NONE
!------------------------------------------------------------------------------
TYPE(Solver_t) :: Solver
TYPE(Solver_t), TARGET :: Solver
TYPE(Model_t) :: Model


Expand All @@ -65,7 +65,7 @@ SUBROUTINE AdjointSolver( Model,Solver,dt,TransientSimulation )
!------------------------------------------------------------------------------
! Local variables
!------------------------------------------------------------------------------
TYPE(Solver_t),Pointer :: NSSolver
TYPE(Solver_t),POINTER :: NSSolver, PSolver
TYPE(Matrix_t),POINTER :: InitMat,TransMat,StiffMatrix
TYPE(ValueList_t),POINTER :: BC,SolverParams
TYPE(Nodes_t) :: ElementNodes
Expand Down Expand Up @@ -237,7 +237,8 @@ SUBROUTINE AdjointSolver( Model,Solver,dt,TransientSimulation )
End Do
EndDo

CALL FinishAssembly( Solver, ForceVector )
PSolver => Solver
CALL FinishAssembly( PSolver, ForceVector )

CALL DefaultDirichletBCs()

Expand Down
2 changes: 1 addition & 1 deletion fem/src/SolverUtils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9998,7 +9998,7 @@ END SUBROUTINE InitializeTimestep
!------------------------------------------------------------------------------
SUBROUTINE FinishAssembly( Solver, ForceVector )
!------------------------------------------------------------------------------
TYPE(Solver_t) :: Solver
TYPE(Solver_t),POINTER :: Solver
REAL(KIND=dp) :: ForceVector(:)
INTEGER :: Order
LOGICAL :: Found
Expand Down
15 changes: 9 additions & 6 deletions fem/src/modules/ArteryOutlet.F90
Original file line number Diff line number Diff line change
Expand Up @@ -51,10 +51,10 @@ SUBROUTINE OutletCompute_Init( Model,Solver,dt,TransientSimulation )
IMPLICIT NONE
!------------------------------------------------------------------------------
TYPE(Model_t) :: Model
TYPE(Solver_t) :: Solver
TYPE(Solver_t),TARGET :: Solver
REAL(KIND=dp) :: dt
LOGICAL :: TransientSimulation
!------------------------------------------------------------------------------
!------------------------------------------------------------------------------
TYPE(ValueList_t), POINTER :: Params
TYPE(Mesh_t), POINTER :: Mesh, PMesh

Expand Down Expand Up @@ -100,7 +100,7 @@ SUBROUTINE OutletCompute( Model,Solver,dt,TransientSimulation )
IMPLICIT NONE
!------------------------------------------------------------------------------
TYPE(Model_t) :: Model
TYPE(Solver_t):: Solver
TYPE(Solver_t), TARGET :: Solver
REAL(KIND=dp) :: dt
LOGICAL :: TransientSimulation

Expand All @@ -114,7 +114,7 @@ SUBROUTINE OutletCompute( Model,Solver,dt,TransientSimulation )
TYPE(ValueList_t), POINTER :: Material
TYPE(Variable_t), POINTER :: LVar, FlowSol
TYPE(Mesh_t), POINTER :: Mesh1D, Mesh3D
TYPE(Solver_t), POINTER :: FlowSolver
TYPE(Solver_t), POINTER :: FlowSolver, PSolver

INTEGER :: t, k,n,m,ie,bf_id,mat_id,prev_mat_id,istat,LocalNodes,i,j, nonliniter, l, &
bc, joinnode, Connections, SolidConnections, fsstep, fsstepmax, NonlinearIter, &
Expand Down Expand Up @@ -158,7 +158,10 @@ SUBROUTINE OutletCompute( Model,Solver,dt,TransientSimulation )
CALL Info('OutletCompute','Starting')

Mesh1D => Solver % Mesh


PSolver => Solver
! IF (.NOT.ASSOCIATED(PSolver)) CALL FATAL('OutletCompute','Solver pointer not associated')

Wnodal => Solver % Variable % Values
LocalNodes = SIZE( Wnodal )

Expand Down Expand Up @@ -546,7 +549,7 @@ SUBROUTINE OutletCompute( Model,Solver,dt,TransientSimulation )
! Dirichlet boundary settings. Actually no need to call it except for
! transient simulations.
!------------------------------------------------------------------------------
CALL FinishAssembly( Solver,ForceVector )
CALL FinishAssembly( PSolver, ForceVector )

FirstTime = .FALSE.

Expand Down
9 changes: 5 additions & 4 deletions fem/src/modules/DCRComplexSolve.F90
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ SUBROUTINE DCRComplexSolver( Model,Solver,dt,TransientSimulation )

IMPLICIT NONE
!------------------------------------------------------------------------------
TYPE(Solver_t) :: Solver
TYPE(Solver_t),TARGET :: Solver
TYPE(Model_t) :: Model

REAL(KIND=dp) :: dt
Expand All @@ -60,7 +60,8 @@ SUBROUTINE DCRComplexSolver( Model,Solver,dt,TransientSimulation )
TYPE(Matrix_t),POINTER :: StiffMatrix
TYPE(Nodes_t) :: ElementNodes
TYPE(Element_t),POINTER :: CurrentElement

TYPE(Solver_t),POINTER :: PSolver

INTEGER, POINTER :: NodeIndexes(:)

LOGICAL :: AllocationsDone = .FALSE., Bubbles, GotIt, notScalar = .TRUE., stat
Expand Down Expand Up @@ -366,8 +367,8 @@ END FUNCTION DCRInsideResidual
!------------------------------------------------------------------------------
END DO
!------------------------------------------------------------------------------

CALL FinishAssembly( Solver, ForceVector )
PSolver => Solver
CALL FinishAssembly( PSolver, ForceVector )
!
! Dirichlet BCs:
! --------------
Expand Down
4 changes: 2 additions & 2 deletions fem/src/modules/PhaseChangeSolve.F90
Original file line number Diff line number Diff line change
Expand Up @@ -394,7 +394,7 @@ SUBROUTINE PhaseChangeSolve( Model,Solver,dt,TransientSimulation )
ForceVector, LocalForceVector, n, 1, SurfPerm(NodeIndexes) )
END DO

CALL FinishAssembly( Solver, ForceVector )
CALL FinishAssembly( PSolver, ForceVector )

! No Dirihtlet conditions here since
! One should not really try to force the phase change at some point,
Expand Down Expand Up @@ -465,7 +465,7 @@ SUBROUTINE PhaseChangeSolve( Model,Solver,dt,TransientSimulation )
ForceVector, LocalForceVector, n, 1, SurfPerm(NodeIndexes) )
END DO

CALL FinishAssembly( Solver, ForceVector )
CALL FinishAssembly( PSolver, ForceVector )
CALL SolveSystem( StiffMatrix, ParMatrix, ForceVector, Surface, Norm, 1, Solver )
END IF

Expand Down
4 changes: 3 additions & 1 deletion fem/src/modules/TransportEquation.F90
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@ SUBROUTINE TransportEquationSolver( Model, Solver, dt, TransientSimulation )
TYPE(Variable_t), POINTER :: FlowSol, Udot0Var
TYPE(VariablePtr_t), POINTER :: U0Var(:)
TYPE(ValueList_t), POINTER :: Material
TYPE(Solver_t), POINTER :: PSolver

INTEGER :: i,j,k,p,n,t,body_id,bf_id,istat,LocalNodes,&
AdvectionVariableComponents, VelocityComponents
Expand Down Expand Up @@ -417,7 +418,8 @@ SUBROUTINE TransportEquationSolver( Model, Solver, dt, TransientSimulation )
! Dirichlet boundary settings. Actually no need to call it except for
! transient simulations.
!------------------------------------------------------------------------------
CALL FinishAssembly( Solver, ForceVector )
PSolver => Solver
CALL FinishAssembly( PSolver, ForceVector )

!------------------------------------------------------------------------------
! Dirichlet boundary conditions
Expand Down

0 comments on commit 044b15d

Please sign in to comment.