Loading [MathJax]/extensions/tex2jax.js
Neko 0.9.99
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
krylov.f90
Go to the documentation of this file.
1! Copyright (c) 2020-2023, The Neko Authors
2! All rights reserved.
3!
4! Redistribution and use in source and binary forms, with or without
5! modification, are permitted provided that the following conditions
6! are met:
7!
8! * Redistributions of source code must retain the above copyright
9! notice, this list of conditions and the following disclaimer.
10!
11! * Redistributions in binary form must reproduce the above
12! copyright notice, this list of conditions and the following
13! disclaimer in the documentation and/or other materials provided
14! with the distribution.
15!
16! * Neither the name of the authors nor the names of its
17! contributors may be used to endorse or promote products derived
18! from this software without specific prior written permission.
19!
20! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31! POSSIBILITY OF SUCH DAMAGE.
32!
34module krylov
35 use gather_scatter, only : gs_t, gs_op_add
36 use ax_product, only : ax_t
37 use num_types, only: rp, c_rp
38 use precon, only : pc_t
39 use coefs, only : coef_t
40 use mesh, only : mesh_t
41 use field, only : field_t
42 use utils, only : neko_error, neko_warning
43 use bc_list, only : bc_list_t
44 use identity, only : ident_t
47 use logger, only : neko_log, log_size
48 implicit none
49 private
50
51 integer, public, parameter :: ksp_max_iter = 1e3
52 real(kind=rp), public, parameter :: ksp_abs_tol = 1d-9
53 real(kind=rp), public, parameter :: ksp_rel_tol = 1d-9
54
56 type, public :: ksp_monitor_t
58 integer :: iter
60 real(kind=rp) :: res_start
62 real(kind=rp) :: res_final
64 logical :: converged = .false.
65 end type ksp_monitor_t
66
68 type, public, abstract :: ksp_t
69 class(pc_t), pointer :: m => null()
70 real(kind=rp) :: rel_tol
71 real(kind=rp) :: abs_tol
72 integer :: max_iter
73 class(pc_t), allocatable :: m_ident
74 logical :: monitor
75 contains
77 procedure(ksp_init_intrf), deferred, pass(this) :: init
79 procedure, pass(this) :: ksp_init => krylov_init
81 procedure, pass(this) :: ksp_free => krylov_free
83 procedure, pass(this) :: set_pc => krylov_set_pc
85 procedure(ksp_method), pass(this), deferred :: solve
87 procedure(ksp_method_coupled), pass(this), deferred :: solve_coupled
89 procedure, pass(this) :: monitor_start => krylov_monitor_start
91 procedure, pass(this) :: monitor_stop => krylov_monitor_stop
93 procedure, pass(this) :: monitor_iter => krylov_monitor_iter
95 procedure, pass(this) :: is_converged => krylov_is_converged
97 procedure(ksp_t_free), pass(this), deferred :: free
98 end type ksp_t
99
107 abstract interface
108 subroutine ksp_init_intrf(this, n, max_iter, M, rel_tol, abs_tol, monitor)
109 import :: pc_t, ksp_t, rp
110 implicit none
111 class(ksp_t), target, intent(inout) :: this
112 integer, intent(in) :: max_iter
113 class(pc_t), optional, intent(in), target :: M
114 integer, intent(in) :: n
115 real(kind=rp), optional, intent(in) :: rel_tol
116 real(kind=rp), optional, intent(in) :: abs_tol
117 logical, optional, intent(in) :: monitor
118 end subroutine ksp_init_intrf
119 end interface
120
130 abstract interface
131 function ksp_method(this, Ax, x, f, n, coef, blst, gs_h, niter) &
132 result(ksp_results)
133 import :: bc_list_t
134 import :: field_t
135 import :: ksp_t
136 import :: coef_t
137 import :: gs_t
138 import :: ax_t
139 import :: ksp_monitor_t
140 import rp
141 implicit none
142 class(ksp_t), intent(inout) :: this
143 class(ax_t), intent(in) :: ax
144 type(field_t), intent(inout) :: x
145 integer, intent(in) :: n
146 real(kind=rp), dimension(n), intent(in) :: f
147 type(coef_t), intent(inout) :: coef
148 type(bc_list_t), intent(inout) :: blst
149 type(gs_t), intent(inout) :: gs_h
150 integer, optional, intent(in) :: niter
151 type(ksp_monitor_t) :: ksp_results
152 end function ksp_method
153 end interface
154
168 abstract interface
169 function ksp_method_coupled(this, Ax, x, y, z, fx, fy, fz, &
170 n, coef, blstx, blsty, blstz, gs_h, niter) result(ksp_results)
171 import :: bc_list_t
172 import :: field_t
173 import :: ksp_t
174 import :: coef_t
175 import :: gs_t
176 import :: ax_t
177 import :: ksp_monitor_t
178 import rp
179 implicit none
180 class(ksp_t), intent(inout) :: this
181 class(ax_t), intent(in) :: ax
182 type(field_t), intent(inout) :: x
183 type(field_t), intent(inout) :: y
184 type(field_t), intent(inout) :: z
185 integer, intent(in) :: n
186 real(kind=rp), dimension(n), intent(in) :: fx
187 real(kind=rp), dimension(n), intent(in) :: fy
188 real(kind=rp), dimension(n), intent(in) :: fz
189 type(coef_t), intent(inout) :: coef
190 type(bc_list_t), intent(inout) :: blstx
191 type(bc_list_t), intent(inout) :: blsty
192 type(bc_list_t), intent(inout) :: blstz
193 type(gs_t), intent(inout) :: gs_h
194 integer, optional, intent(in) :: niter
195 type(ksp_monitor_t), dimension(3) :: ksp_results
196 end function ksp_method_coupled
197 end interface
198
200 abstract interface
201 subroutine ksp_t_free(this)
202 import :: ksp_t
203 class(ksp_t), intent(inout) :: this
204 end subroutine ksp_t_free
205 end interface
206
207 interface
208
216 module subroutine krylov_solver_factory(object, n, type_name, &
217 max_iter, abstol, m, monitor)
218 class(ksp_t), allocatable, intent(inout) :: object
219 integer, intent(in), value :: n
220 character(len=*), intent(in) :: type_name
221 integer, intent(in) :: max_iter
222 real(kind=rp), optional :: abstol
223 class(pc_t), optional, intent(in), target :: m
224 logical, optional, intent(in) :: monitor
225 end subroutine krylov_solver_factory
226
227 end interface
228
229 public :: krylov_solver_factory
230contains
231
237 subroutine krylov_init(this, max_iter, rel_tol, abs_tol, M, monitor)
238 class(ksp_t), target, intent(inout) :: this
239 integer, intent(in) :: max_iter
240 real(kind=rp), optional, intent(in) :: rel_tol
241 real(kind=rp), optional, intent(in) :: abs_tol
242 class(pc_t), optional, target, intent(in) :: m
243 logical, optional, intent(in) :: monitor
244
245 call krylov_free(this)
246
247 if (present(rel_tol)) then
248 this%rel_tol = rel_tol
249 else
250 this%rel_tol = ksp_rel_tol
251 end if
252
253 if (present(abs_tol)) then
254 this%abs_tol = abs_tol
255 else
256 this%abs_tol = ksp_abs_tol
257 end if
258
259 this%max_iter = max_iter
260
261 if (present(m)) then
262 this%M => m
263 else
264 if (.not. associated(this%M)) then
265 if (neko_bcknd_device .eq. 1) then
266 allocate(device_ident_t::this%M_ident)
267 else
268 allocate(ident_t::this%M_ident)
269 end if
270 this%M => this%M_ident
271 end if
272 end if
273
274 if (present(monitor)) then
275 this%monitor = monitor
276 else
277 this%monitor = .false.
278 end if
279
280 end subroutine krylov_init
281
283 subroutine krylov_free(this)
284 class(ksp_t), intent(inout) :: this
285
287
288 end subroutine krylov_free
289
292 subroutine krylov_set_pc(this, M)
293 class(ksp_t), intent(inout) :: this
294 class(pc_t), target, intent(in) :: M
295
296 if (associated(this%M)) then
297 select type (pc => this%M)
298 type is (ident_t)
299 type is (device_ident_t)
300 class default
301 call neko_error('Preconditioner already defined')
302 end select
303 end if
304
305 this%M => m
306
307 end subroutine krylov_set_pc
308
310 subroutine krylov_monitor_start(this, name)
311 class(ksp_t), intent(in) :: this
312 character(len=*) :: name
313 character(len=LOG_SIZE) :: log_buf
314
315 if (this%monitor) then
316 write(log_buf, '(A)') 'Krylov monitor (' // trim(name) // ')'
317 call neko_log%section(trim(log_buf))
318 call neko_log%newline()
319 call neko_log%begin()
320 write(log_buf, '(A)') ' Iter. Residual'
321 call neko_log%message(log_buf)
322 write(log_buf, '(A)') '---------------------'
323 call neko_log%message(log_buf)
324 end if
325 end subroutine krylov_monitor_start
326
328 subroutine krylov_monitor_stop(this)
329 class(ksp_t), intent(in) :: this
330
331 if (this%monitor) then
332 call neko_log%end()
333 call neko_log%end_section()
334 call neko_log%newline()
335 end if
336 end subroutine krylov_monitor_stop
337
338
340 subroutine krylov_monitor_iter(this, iter, rnorm)
341 class(ksp_t), intent(in) :: this
342 integer, intent(in) :: iter
343 real(kind=rp), intent(in) :: rnorm
344 character(len=LOG_SIZE) :: log_buf
345
346 if (this%monitor) then
347 write(log_buf, '(I6,E15.7)') iter, rnorm
348 call neko_log%message(log_buf)
349 end if
350
351 end subroutine krylov_monitor_iter
352
361 pure function krylov_is_converged(this, iter, residual) result(converged)
362 class(ksp_t), intent(in) :: this
363 integer, intent(in) :: iter
364 real(kind=rp), intent(in) :: residual
365 logical :: converged
366
367 converged = .true.
368 if (iter .ge. this%max_iter) converged = .false.
369 if (residual .gt. this%abs_tol) converged = .false.
370
371 end function krylov_is_converged
372
373end module krylov
Abstract interface for a Krylov method's constructor.
Definition krylov.f90:108
Abstract interface for a Krylov method's coupled solve routine.
Definition krylov.f90:169
Abstract interface for a Krylov method's solve routine.
Definition krylov.f90:131
Abstract interface for deallocating a Krylov method.
Definition krylov.f90:201
Defines a Matrix-vector product.
Definition ax.f90:34
Defines a list of bc_t.
Definition bc_list.f90:34
Coefficients.
Definition coef.f90:34
Identity Krylov preconditioner for accelerators.
Defines a field.
Definition field.f90:34
Gather-scatter.
Krylov preconditioner (identity)
Implements the base abstract type for Krylov solvers plus helper types.
Definition krylov.f90:34
real(kind=rp), parameter, public ksp_rel_tol
Relative tolerance.
Definition krylov.f90:53
real(kind=rp), parameter, public ksp_abs_tol
Absolut tolerance.
Definition krylov.f90:52
subroutine krylov_free(this)
Deallocate a Krylov solver.
Definition krylov.f90:284
integer, parameter, public ksp_max_iter
Maximum number of iters.
Definition krylov.f90:51
subroutine krylov_monitor_iter(this, iter, rnorm)
Monitor iteration.
Definition krylov.f90:341
subroutine krylov_init(this, max_iter, rel_tol, abs_tol, m, monitor)
Factory for Krylov solvers. Both creates and initializes the object.
Definition krylov.f90:238
subroutine krylov_monitor_start(this, name)
Monitor start.
Definition krylov.f90:311
pure logical function krylov_is_converged(this, iter, residual)
Check for convergence.
Definition krylov.f90:362
subroutine krylov_set_pc(this, m)
Setup a Krylov solver's preconditioner.
Definition krylov.f90:293
subroutine krylov_monitor_stop(this)
Monitor stop.
Definition krylov.f90:329
Logging routines.
Definition log.f90:34
type(log_t), public neko_log
Global log stream.
Definition log.f90:65
integer, parameter, public log_size
Definition log.f90:42
Defines a mesh.
Definition mesh.f90:34
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public c_rp
Definition num_types.f90:13
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Krylov preconditioner.
Definition precon.f90:34
Utilities.
Definition utils.f90:35
subroutine, public neko_warning(warning_msg)
Reports a warning to standard output.
Definition utils.f90:266
Base type for a matrix-vector product providing .
Definition ax.f90:43
A list of allocatable `bc_t`. Follows the standard interface of lists.
Definition bc_list.f90:47
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
Defines a canonical Krylov preconditioner for accelerators.
Defines a canonical Krylov preconditioner.
Type for storing initial and final residuals in a Krylov solver.
Definition krylov.f90:56
Base abstract type for a canonical Krylov method, solving .
Definition krylov.f90:68
Defines a canonical Krylov preconditioner.
Definition precon.f90:40