FE-Project
Loading...
Searching...
No Matches
scale_gmres.F90
Go to the documentation of this file.
1!-------------------------------------------------------------------------------
2!> Module common / GMRES
3!!
4!! @par Description
5!! A module to provide a iterative solver for system of linear equations using generalized minimal residual method (GMRES)
6!!
7!! @par Reference
8!! - Y. Saad and M.H. Schultz, 1986:
9!! GMRES: A generalized minimal residual algorithm for solving nonsymmetric linear systems.
10!! SIAM J. Sci. Stat. Comput., 7:856–869
11!!
12!! @author Yuta Kawai, Team SCALE
13!!
14#include "scaleFElib.h"
16 !-----------------------------------------------------------------------------
17 !
18 !++ used modules
19 !
20 use scale_precision
21 use scale_prc
22
23 !-----------------------------------------------------------------------------
24 implicit none
25 private
26
27 !-----------------------------------------------------------------------------
28 !
29 !++ Public type
30 !
31
32 !> Derived type to provide a iterative solver for system of linear equations using GMRES
33 type, public :: gmres
34 real(rp) :: eps
35 real(rp) :: eps0
36 integer :: n
37 integer :: m
38 integer :: m_out
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(:)
46 contains
47 procedure, public :: init => gmres_init
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
52 end type
53
54 !-----------------------------------------------------------------------------
55 !
56 !++ Public parameters & variables
57 !
58
59 !-----------------------------------------------------------------------------
60 !
61 !++ Private procedure
62 !
63
64 !-----------------------------------------------------------------------------
65 !
66 !++ Private parameters & variables
67 !
68
69 !-----------------------------------------------------------------------------
70
71 ! Private procedure
72 !
73
74 ! Private variable
75 !
76
77contains
78
79subroutine gmres_init( this, N, m, eps, eps0 )
80
81 implicit none
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
87
88 !--------------------------------------
89
90 this%N = n
91 this%m = m
92 this%EPS = eps
93 this%EPS0 = eps0
94
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) )
101
102 return
103end subroutine gmres_init
104
105!OCL SERIAL
106subroutine gmres_iterate_pre( this, b, w0, is_converged )
107 implicit none
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
112
113 integer :: i
114 !--------------------------------------
115
116 this%g(1) = 0.0_rp
117 do i=1, this%N
118 this%v(i,1) = b(i) - w0(i)
119 this%g(1) = this%g(1) + this%v(i,1)**2
120 end do
121 this%g(1) = sqrt(this%g(1))
122
123 if ( this%g(1) < this%EPS0 * this%N ) then
124 is_converged = .true.
125 return
126 else
127 is_converged = .false.
128 end if
129
130 do i=1, this%N
131 this%v(i,1) = this%v(i,1) / this%g(1)
132 end do
133
134 this%m_out = min(this%m, this%N)
135 return
136end subroutine gmres_iterate_pre
137
138!OCL SERIAL
139subroutine gmres_iterate_step_j( this, j, wj, is_converged )
140 implicit none
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
145
146 integer :: i
147 real(RP) :: tmp1, tmp2
148 !--------------------------------------
149
150 do i=1, j
151 this%hj(i) = sum( wj(:) * this%v(:,i) )
152 wj(:) = wj(:) - this%hj(i) * this%v(:,i)
153 end do
154 this%hj(j+1) = sqrt( sum(wj(:)**2) )
155
156 ! if ( abs(this%hj(j+1)) < this%EPS0 ) then
157 ! this%m_out = j
158 ! is_converged = .true.
159 ! return
160 ! else
161 this%v(:,j+1) = wj(:) / this%hj(j+1)
162 ! end if
163
164 this%r(1,j) = this%hj(1)
165 do i=1, j-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)
168 this%r(i ,j) = tmp1
169 this%r(i+1,j) = tmp2
170 end do
171
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)
175
176 this%g(j+1) = - this%si(j) * this%g(j)
177 this%g(j) = this%co(j) * this%g(j)
178
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
181
182 if ( abs(this%g(j+1)) < this%EPS ) then
183 this%m_out = j
184 is_converged = .true.
185 else
186 is_converged = .false.
187 end if
188
189 return
190end subroutine gmres_iterate_step_j
191
192!OCL SERIAL
193subroutine gmres_iterate_post( this, x )
194 implicit none
195 class(gmres), intent(inout) :: this
196 real(RP), intent(inout) :: x(this%N)
197
198 integer :: i, j
199 !--------------------------------------
200
201 do j=this%m_out, 1, -1
202 this%y(j) = this%g(j)
203 do i=j+1, this%m_out
204 this%y(j) = this%y(j) - this%r(j,i) * this%y(i)
205 end do
206 this%y(j) = this%y(j) / this%r(j,j)
207 end do
208
209 x(:) = x(:) + matmul(this%v(:,1:this%m_out), this%y(1:this%m_out))
210
211 return
212end subroutine gmres_iterate_post
213
214subroutine gmres_final( this )
215 implicit none
216 class(gmres), intent(inout) :: this
217 !--------------------------------------
218
219 if ( allocated(this%v) ) then
220 deallocate( this%v )
221 deallocate( this%hj )
222 deallocate( this%g )
223 deallocate( this%r )
224 deallocate( this%co, this%si )
225 deallocate( this%y )
226 end if
227
228 return
229end subroutine gmres_final
230
231end module scale_gmres
Module common / GMRES.
subroutine gmres_init(this, n, m, eps, eps0)
Derived type to provide a iterative solver for system of linear equations using GMRES.