Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
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, pass(this) :: ksp_init => krylov_init
79 procedure, pass(this) :: ksp_free => krylov_free
81 procedure, pass(this) :: set_pc => krylov_set_pc
83 procedure(ksp_method), pass(this), deferred :: solve
85 procedure(ksp_method_coupled), pass(this), deferred :: solve_coupled
87 procedure, pass(this) :: monitor_start => krylov_monitor_start
89 procedure, pass(this) :: monitor_stop => krylov_monitor_stop
91 procedure, pass(this) :: monitor_iter => krylov_monitor_iter
93 procedure, pass(this) :: is_converged => krylov_is_converged
95 procedure(ksp_t_free), pass(this), deferred :: free
96 end type ksp_t
97
98
108 abstract interface
109 function ksp_method(this, Ax, x, f, n, coef, blst, gs_h, niter) &
110 result(ksp_results)
111 import :: bc_list_t
112 import :: field_t
113 import :: ksp_t
114 import :: coef_t
115 import :: gs_t
116 import :: ax_t
117 import :: ksp_monitor_t
118 import rp
119 implicit none
120 class(ksp_t), intent(inout) :: this
121 class(ax_t), intent(in) :: ax
122 type(field_t), intent(inout) :: x
123 integer, intent(in) :: n
124 real(kind=rp), dimension(n), intent(in) :: f
125 type(coef_t), intent(inout) :: coef
126 type(bc_list_t), intent(inout) :: blst
127 type(gs_t), intent(inout) :: gs_h
128 integer, optional, intent(in) :: niter
129 type(ksp_monitor_t) :: ksp_results
130 end function ksp_method
131 end interface
132
146 abstract interface
147 function ksp_method_coupled(this, Ax, x, y, z, fx, fy, fz, &
148 n, coef, blstx, blsty, blstz, gs_h, niter) result(ksp_results)
149 import :: bc_list_t
150 import :: field_t
151 import :: ksp_t
152 import :: coef_t
153 import :: gs_t
154 import :: ax_t
155 import :: ksp_monitor_t
156 import rp
157 implicit none
158 class(ksp_t), intent(inout) :: this
159 class(ax_t), intent(in) :: ax
160 type(field_t), intent(inout) :: x
161 type(field_t), intent(inout) :: y
162 type(field_t), intent(inout) :: z
163 integer, intent(in) :: n
164 real(kind=rp), dimension(n), intent(in) :: fx
165 real(kind=rp), dimension(n), intent(in) :: fy
166 real(kind=rp), dimension(n), intent(in) :: fz
167 type(coef_t), intent(inout) :: coef
168 type(bc_list_t), intent(inout) :: blstx
169 type(bc_list_t), intent(inout) :: blsty
170 type(bc_list_t), intent(inout) :: blstz
171 type(gs_t), intent(inout) :: gs_h
172 integer, optional, intent(in) :: niter
173 type(ksp_monitor_t), dimension(3) :: ksp_results
174 end function ksp_method_coupled
175 end interface
176
178 abstract interface
179 subroutine ksp_t_free(this)
180 import :: ksp_t
181 class(ksp_t), intent(inout) :: this
182 end subroutine ksp_t_free
183 end interface
184
185 interface
186
194 module subroutine krylov_solver_factory(object, n, type_name, &
195 max_iter, abstol, m, monitor)
196 class(ksp_t), allocatable, intent(inout) :: object
197 integer, intent(in), value :: n
198 character(len=*), intent(in) :: type_name
199 integer, intent(in) :: max_iter
200 real(kind=rp), optional :: abstol
201 class(pc_t), optional, intent(in), target :: m
202 logical, optional, intent(in) :: monitor
203 end subroutine krylov_solver_factory
204
206 module subroutine krylov_solver_destroy(object)
207 class(ksp_t), allocatable, intent(inout) :: object
208 end subroutine krylov_solver_destroy
209 end interface
210
211 public :: krylov_solver_factory, krylov_solver_destroy
212contains
213
219 subroutine krylov_init(this, max_iter, rel_tol, abs_tol, M, monitor)
220 class(ksp_t), target, intent(inout) :: this
221 integer, intent(in) :: max_iter
222 real(kind=rp), optional, intent(in) :: rel_tol
223 real(kind=rp), optional, intent(in) :: abs_tol
224 class(pc_t), optional, target, intent(in) :: m
225 logical, optional, intent(in) :: monitor
226
227 call krylov_free(this)
228
229 if (present(rel_tol)) then
230 this%rel_tol = rel_tol
231 else
232 this%rel_tol = ksp_rel_tol
233 end if
234
235 if (present(abs_tol)) then
236 this%abs_tol = abs_tol
237 else
238 this%abs_tol = ksp_abs_tol
239 end if
240
241 this%max_iter = max_iter
242
243 if (present(m)) then
244 this%M => m
245 else
246 if (.not. associated(this%M)) then
247 if (neko_bcknd_device .eq. 1) then
248 allocate(device_ident_t::this%M_ident)
249 else
250 allocate(ident_t::this%M_ident)
251 end if
252 this%M => this%M_ident
253 end if
254 end if
255
256 if (present(monitor)) then
257 this%monitor = monitor
258 else
259 this%monitor = .false.
260 end if
261
262 end subroutine krylov_init
263
265 subroutine krylov_free(this)
266 class(ksp_t), intent(inout) :: this
267
269
270 end subroutine krylov_free
271
274 subroutine krylov_set_pc(this, M)
275 class(ksp_t), intent(inout) :: this
276 class(pc_t), target, intent(in) :: M
277
278 if (associated(this%M)) then
279 select type (pc => this%M)
280 type is (ident_t)
281 type is (device_ident_t)
282 class default
283 call neko_error('Preconditioner already defined')
284 end select
285 end if
286
287 this%M => m
288
289 end subroutine krylov_set_pc
290
292 subroutine krylov_monitor_start(this, name)
293 class(ksp_t), intent(in) :: this
294 character(len=*) :: name
295 character(len=LOG_SIZE) :: log_buf
296
297 if (this%monitor) then
298 write(log_buf, '(A)') 'Krylov monitor (' // trim(name) // ')'
299 call neko_log%section(trim(log_buf))
300 call neko_log%newline()
301 call neko_log%begin()
302 write(log_buf, '(A)') ' Iter. Residual'
303 call neko_log%message(log_buf)
304 write(log_buf, '(A)') '---------------------'
305 call neko_log%message(log_buf)
306 end if
307 end subroutine krylov_monitor_start
308
310 subroutine krylov_monitor_stop(this)
311 class(ksp_t), intent(in) :: this
312
313 if (this%monitor) then
314 call neko_log%end()
315 call neko_log%end_section()
316 call neko_log%newline()
317 end if
318 end subroutine krylov_monitor_stop
319
320
322 subroutine krylov_monitor_iter(this, iter, rnorm)
323 class(ksp_t), intent(in) :: this
324 integer, intent(in) :: iter
325 real(kind=rp), intent(in) :: rnorm
326 character(len=LOG_SIZE) :: log_buf
327
328 if (this%monitor) then
329 write(log_buf, '(I6,E15.7)') iter, rnorm
330 call neko_log%message(log_buf)
331 end if
332
333 end subroutine krylov_monitor_iter
334
343 pure function krylov_is_converged(this, iter, residual) result(converged)
344 class(ksp_t), intent(in) :: this
345 integer, intent(in) :: iter
346 real(kind=rp), intent(in) :: residual
347 logical :: converged
348
349 converged = .true.
350 if (iter .ge. this%max_iter) converged = .false.
351 if (residual .gt. this%abs_tol) converged = .false.
352
353 end function krylov_is_converged
354
355end module krylov
Abstract interface for a Krylov method's coupled solve routine.
Definition krylov.f90:147
Abstract interface for a Krylov method's solve routine.
Definition krylov.f90:109
Abstract interface for deallocating a Krylov method.
Definition krylov.f90:179
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:266
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:323
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:220
subroutine krylov_monitor_start(this, name)
Monitor start.
Definition krylov.f90:293
pure logical function krylov_is_converged(this, iter, residual)
Check for convergence.
Definition krylov.f90:344
subroutine krylov_set_pc(this, m)
Setup a Krylov solver's preconditioner.
Definition krylov.f90:275
subroutine krylov_monitor_stop(this)
Monitor stop.
Definition krylov.f90:311
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:46
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