Neko  0.8.1
A portable framework for high-order spectral element flow simulations
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 !
34 module 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, only : bc_list_t
44  use identity, only : ident_t
46  use neko_config
47  implicit none
48  private
49 
50  integer, public, parameter :: ksp_max_iter = 1e4
51  real(kind=rp), public, parameter :: ksp_abs_tol = 1d-9
52  real(kind=rp), public, parameter :: ksp_rel_tol = 1d-9
53 
55  type, public :: ksp_monitor_t
57  integer :: iter
59  real(kind=rp) :: res_start
61  real(kind=rp) :: res_final
62  end type ksp_monitor_t
63 
65  type, public, abstract :: ksp_t
66  class(pc_t), pointer :: m => null()
67  real(kind=rp) :: rel_tol
68  real(kind=rp) :: abs_tol
69  integer :: max_iter
70  class(pc_t), allocatable :: m_ident
71  contains
73  procedure, pass(this) :: ksp_init => krylov_init
75  procedure, pass(this) :: ksp_free => krylov_free
77  procedure, pass(this) :: set_pc => krylov_set_pc
79  procedure(ksp_method), pass(this), deferred :: solve
81  procedure(ksp_t_free), pass(this), deferred :: free
82  end type ksp_t
83 
84 
94  abstract interface
95  function ksp_method(this, Ax, x, f, n, coef, blst, gs_h, niter) result(ksp_results)
96  import :: bc_list_t
97  import :: field_t
98  import :: ksp_t
99  import :: coef_t
100  import :: gs_t
101  import :: ax_t
102  import :: ksp_monitor_t
103  import rp
104  implicit none
105  class(ksp_t), intent(inout) :: this
106  class(ax_t), intent(inout) :: ax
107  type(field_t), intent(inout) :: x
108  integer, intent(in) :: n
109  real(kind=rp), dimension(n), intent(inout) :: f
110  type(coef_t), intent(inout) :: coef
111  type(bc_list_t), intent(inout) :: blst
112  type(gs_t), intent(inout) :: gs_h
113  integer, optional, intent(in) :: niter
114  type(ksp_monitor_t) :: ksp_results
115  end function ksp_method
116  end interface
117 
119  abstract interface
120  subroutine ksp_t_free(this)
121  import :: ksp_t
122  class(ksp_t), intent(inout) :: this
123  end subroutine ksp_t_free
124  end interface
125 
126 contains
127 
133  subroutine krylov_init(this, max_iter, rel_tol, abs_tol, M)
134  class(ksp_t), target, intent(inout) :: this
135  integer, intent(in) :: max_iter
136  real(kind=rp), optional, intent(in) :: rel_tol
137  real(kind=rp), optional, intent(in) :: abs_tol
138  class(pc_t), optional, target, intent(in) :: m
139 
140  call krylov_free(this)
141 
142  if (present(rel_tol)) then
143  this%rel_tol = rel_tol
144  else
145  this%rel_tol = ksp_rel_tol
146  end if
147 
148  if (present(abs_tol)) then
149  this%abs_tol = abs_tol
150  else
151  this%abs_tol = ksp_abs_tol
152  end if
153 
154  this%max_iter = max_iter
155 
156  if (present(m)) then
157  this%M => m
158  else
159  if (.not. associated(this%M)) then
160  if (neko_bcknd_device .eq. 1) then
161  allocate(device_ident_t::this%M_ident)
162  else
163  allocate(ident_t::this%M_ident)
164  end if
165  this%M => this%M_ident
166  end if
167  end if
168 
169  end subroutine krylov_init
170 
172  subroutine krylov_free(this)
173  class(ksp_t), intent(inout) :: this
174 
176 
177  end subroutine krylov_free
178 
181  subroutine krylov_set_pc(this, M)
182  class(ksp_t), intent(inout) :: this
183  class(pc_t), target, intent(in) :: M
184 
185  if (associated(this%M)) then
186  select type(pc => this%M)
187  type is (ident_t)
188  type is (device_ident_t)
189  class default
190  call neko_error('Preconditioner already defined')
191  end select
192  end if
193 
194  this%M => m
195 
196  end subroutine krylov_set_pc
197 
198 end module krylov
Abstract interface for a Krylov method's solve routine.
Definition: krylov.f90:95
Abstract interface for deallocating a Krylov method.
Definition: krylov.f90:120
Defines a Matrix-vector product.
Definition: ax.f90:34
Defines a boundary condition.
Definition: bc.f90:34
Coefficients.
Definition: coef.f90:34
Identity Krylov preconditioner for accelerators.
Defines a field.
Definition: field.f90:34
Gather-scatter.
Krylov preconditioner (identity)
Definition: pc_identity.f90:34
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:52
real(kind=rp), parameter, public ksp_abs_tol
Absolut tolerance.
Definition: krylov.f90:51
subroutine krylov_free(this)
Deallocate a Krylov solver.
Definition: krylov.f90:173
integer, parameter, public ksp_max_iter
Maximum number of iters.
Definition: krylov.f90:50
subroutine krylov_set_pc(this, M)
Setup a Krylov solver's preconditioner.
Definition: krylov.f90:182
subroutine krylov_init(this, max_iter, rel_tol, abs_tol, M)
Constructor for the base type.
Definition: krylov.f90:134
Defines a mesh.
Definition: mesh.f90:34
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
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 neko_warning(warning_msg)
Definition: utils.f90:191
Base type for a matrix-vector product providing .
Definition: ax.f90:43
A list of boundary conditions.
Definition: bc.f90:102
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:54
Defines a canonical Krylov preconditioner for accelerators.
Defines a canonical Krylov preconditioner.
Definition: pc_identity.f90:42
Type for storing initial and final residuals in a Krylov solver.
Definition: krylov.f90:55
Base abstract type for a canonical Krylov method, solving .
Definition: krylov.f90:65
Defines a canonical Krylov preconditioner.
Definition: precon.f90:40