14#include "scaleFElib.h"
39 real(rp),
allocatable :: v(:,:)
40 real(rp),
allocatable :: hj(:)
41 real(rp),
allocatable :: g(:)
42 real(rp),
allocatable :: r(:,:)
43 real(rp),
allocatable :: co(:)
44 real(rp),
allocatable :: si(:)
45 real(rp),
allocatable :: y(:)
48 procedure,
public :: iterate_pre => gmres_iterate_pre
49 procedure,
public :: iterate_step_j => gmres_iterate_step_j
50 procedure,
public :: iterate_post => gmres_iterate_post
51 procedure,
public :: final => gmres_final
82 class(
gmres),
intent(inout) :: this
83 integer,
intent(in) :: N
84 integer,
intent(in) :: m
85 real(RP),
intent(in) :: eps
86 real(RP),
intent(in) :: eps0
95 allocate( this%v(n,m+1) )
96 allocate( this%hj(m+1) )
97 allocate( this%g(m+1) )
98 allocate( this%r(m+1,m) )
99 allocate( this%co(m), this%si(m) )
100 allocate( this%y(m) )
106subroutine gmres_iterate_pre( this, b, w0, is_converged )
108 class(
gmres),
intent(inout) :: this
109 real(RP),
intent(in) :: b(this%N)
110 real(RP),
intent(in) :: w0(this%N)
111 logical,
intent(out) :: is_converged
118 this%v(i,1) = b(i) - w0(i)
119 this%g(1) = this%g(1) + this%v(i,1)**2
121 this%g(1) = sqrt(this%g(1))
123 if ( this%g(1) < this%EPS0 * this%N )
then
124 is_converged = .true.
127 is_converged = .false.
131 this%v(i,1) = this%v(i,1) / this%g(1)
134 this%m_out = min(this%m, this%N)
136end subroutine gmres_iterate_pre
139subroutine gmres_iterate_step_j( this, j, wj, is_converged )
141 class(
gmres),
intent(inout) :: this
142 integer,
intent(in) :: j
143 real(RP),
intent(inout) :: wj(this%N)
144 logical,
intent(out) :: is_converged
147 real(RP) :: tmp1, tmp2
151 this%hj(i) = sum( wj(:) * this%v(:,i) )
152 wj(:) = wj(:) - this%hj(i) * this%v(:,i)
154 this%hj(j+1) = sqrt( sum(wj(:)**2) )
161 this%v(:,j+1) = wj(:) / this%hj(j+1)
164 this%r(1,j) = this%hj(1)
166 tmp1 = this%co(i) * this%r(i,j) + this%si(i) * this%hj(i+1)
167 tmp2 = - this%si(i) * this%r(i,j) + this%co(i) * this%hj(i+1)
172 tmp1 = 1.0_rp / sqrt(this%r(j,j)**2 + this%hj(j+1)**2)
173 this%co(j) = tmp1 * this%r(j,j)
174 this%si(j) = tmp1 * this%hj(j+1)
176 this%g(j+1) = - this%si(j) * this%g(j)
177 this%g(j) = this%co(j) * this%g(j)
179 this%r(j,j) = this%co(j) * this%r(j,j) + this%si(j) * this%hj(j+1)
180 this%r(j+1,j) = 0.0_rp
182 if ( abs(this%g(j+1)) < this%EPS )
then
184 is_converged = .true.
186 is_converged = .false.
190end subroutine gmres_iterate_step_j
193subroutine gmres_iterate_post( this, x )
195 class(
gmres),
intent(inout) :: this
196 real(RP),
intent(inout) :: x(this%N)
201 do j=this%m_out, 1, -1
202 this%y(j) = this%g(j)
204 this%y(j) = this%y(j) - this%r(j,i) * this%y(i)
206 this%y(j) = this%y(j) / this%r(j,j)
209 x(:) = x(:) + matmul(this%v(:,1:this%m_out), this%y(1:this%m_out))
212end subroutine gmres_iterate_post
214subroutine gmres_final( this )
216 class(
gmres),
intent(inout) :: this
219 if (
allocated(this%v) )
then
221 deallocate( this%hj )
224 deallocate( this%co, this%si )
229end subroutine gmres_final
subroutine gmres_init(this, n, m, eps, eps0)
Derived type to provide a iterative solver for system of linear equations using GMRES.