58     character(len=18) :: name = 
"" 
   62     real(kind=
rp) :: res_start
 
   64     real(kind=
rp) :: res_final
 
   66     logical :: converged = .false.
 
 
   74     class(
pc_t), 
pointer :: m => null() 
 
   75     real(kind=
rp) :: rel_tol 
 
   76     real(kind=
rp) :: abs_tol 
 
   78     class(
pc_t), 
allocatable :: m_ident
 
 
  116       class(
ksp_t), 
target, 
intent(inout) :: this
 
  117       integer, 
intent(in) :: max_iter
 
  118       class(
pc_t), 
optional, 
intent(in), 
target :: M
 
  119       integer, 
intent(in) :: n
 
  120       real(kind=
rp), 
optional, 
intent(in) :: rel_tol
 
  121       real(kind=
rp), 
optional, 
intent(in) :: abs_tol
 
  122       logical, 
optional, 
intent(in) :: monitor
 
 
  136     function ksp_method(this, Ax, x, f, n, coef, blst, gs_h, niter) &
 
  147       class(
ksp_t), 
intent(inout) :: this
 
  148       class(
ax_t), 
intent(in) :: ax
 
  149       type(
field_t), 
intent(inout) :: x
 
  150       integer, 
intent(in) :: n
 
  151       real(kind=
rp), 
dimension(n), 
intent(in) :: f
 
  152       type(
coef_t), 
intent(inout) :: coef
 
  154       type(
gs_t), 
intent(inout) :: gs_h
 
  155       integer, 
optional, 
intent(in) :: niter
 
 
  175          n, coef, blstx, blsty, blstz, gs_h, niter) 
result(ksp_results)
 
  185       class(
ksp_t), 
intent(inout) :: this
 
  186       class(
ax_t), 
intent(in) :: ax
 
  187       type(
field_t), 
intent(inout) :: x
 
  188       type(
field_t), 
intent(inout) :: y
 
  189       type(
field_t), 
intent(inout) :: z
 
  190       integer, 
intent(in) :: n
 
  191       real(kind=
rp), 
dimension(n), 
intent(in) :: fx
 
  192       real(kind=
rp), 
dimension(n), 
intent(in) :: fy
 
  193       real(kind=
rp), 
dimension(n), 
intent(in) :: fz
 
  194       type(
coef_t), 
intent(inout) :: coef
 
  198       type(
gs_t), 
intent(inout) :: gs_h
 
  199       integer, 
optional, 
intent(in) :: niter
 
 
  208       class(
ksp_t), 
intent(inout) :: this
 
 
  221     module subroutine krylov_solver_factory(object, n, type_name, &
 
  222          max_iter, abstol, m, monitor)
 
  223       class(ksp_t), 
allocatable, 
intent(inout) :: object
 
  224       integer, 
intent(in), 
value :: n
 
  225       character(len=*), 
intent(in) :: type_name
 
  226       integer, 
intent(in) :: max_iter
 
  227       real(kind=
rp), 
optional :: abstol
 
  228       class(
pc_t), 
optional, 
intent(in), 
target :: m
 
  229       logical, 
optional, 
intent(in) :: monitor
 
  230     end subroutine krylov_solver_factory
 
  234  public :: krylov_solver_factory
 
  242  subroutine krylov_init(this, max_iter, rel_tol, abs_tol, M, monitor)
 
  243    class(ksp_t), 
target, 
intent(inout) :: this
 
  244    integer, 
intent(in) :: max_iter
 
  245    real(kind=
rp), 
optional, 
intent(in) :: rel_tol
 
  246    real(kind=
rp), 
optional, 
intent(in) :: abs_tol
 
  247    class(
pc_t), 
optional, 
target, 
intent(in) :: m
 
  248    logical, 
optional, 
intent(in) :: monitor
 
  250    call krylov_free(this)
 
  252    if (
present(rel_tol)) 
then 
  253       this%rel_tol = rel_tol
 
  255       this%rel_tol = ksp_rel_tol
 
  258    if (
present(abs_tol)) 
then 
  259       this%abs_tol = abs_tol
 
  261       this%abs_tol = ksp_abs_tol
 
  264    this%max_iter = max_iter
 
  269       if (.not. 
associated(this%M)) 
then 
  273             allocate(
ident_t::this%M_ident)
 
  275          this%M => this%M_ident
 
  279    if (
present(monitor)) 
then 
  280       this%monitor = monitor
 
  282       this%monitor = .false.
 
 
  285  end subroutine krylov_init
 
  288  subroutine krylov_free(this)
 
  289    class(ksp_t), 
intent(inout) :: this
 
 
  293  end subroutine krylov_free
 
  297  subroutine krylov_set_pc(this, M)
 
  298    class(ksp_t), 
intent(inout) :: this
 
  299    class(
pc_t), 
target, 
intent(in) :: M
 
  301    if (
associated(this%M)) 
then 
  302       select type (pc => this%M)
 
  306          call neko_error(
'Preconditioner already defined')
 
 
  312  end subroutine krylov_set_pc
 
  315  subroutine krylov_monitor_start(this, name)
 
  316    class(ksp_t), 
intent(in) :: this
 
  317    character(len=*) :: name
 
  318    character(len=LOG_SIZE) :: log_buf
 
  320    if (this%monitor) 
then 
  321       write(log_buf, 
'(A)') 
'Krylov monitor (' // trim(name) // 
')' 
  322       call neko_log%section(trim(log_buf))
 
  325       write(log_buf, 
'(A)') 
' Iter.          Residual' 
  327       write(log_buf, 
'(A)') 
'-------------------------' 
 
  330  end subroutine krylov_monitor_start
 
  333  subroutine krylov_monitor_stop(this)
 
  334    class(ksp_t), 
intent(in) :: this
 
  336    if (this%monitor) 
then 
 
  341  end subroutine krylov_monitor_stop
 
  345  subroutine krylov_monitor_iter(this, iter, rnorm)
 
  346    class(ksp_t), 
intent(in) :: this
 
  347    integer, 
intent(in) :: iter
 
  348    real(kind=
rp), 
intent(in) :: rnorm
 
  349    character(len=LOG_SIZE) :: log_buf
 
  351    if (this%monitor) 
then 
  352       write(log_buf, 
'(I6,E18.9)') iter, rnorm
 
 
  356  end subroutine krylov_monitor_iter
 
  366  pure function krylov_is_converged(this, iter, residual) 
result(converged)
 
  367    class(ksp_t), 
intent(in) :: this
 
  368    integer, 
intent(in) :: iter
 
  369    real(kind=
rp), 
intent(in) :: residual
 
  373    if (iter .ge. this%max_iter) converged = .false.
 
  374    if (residual .gt. this%abs_tol) converged = .false.
 
 
  376  end function krylov_is_converged
 
  379  subroutine krylov_monitor_print_header(this)
 
  380    class(ksp_monitor_t), 
intent(in) :: this
 
  381    character(len=LOG_SIZE) :: log_buf
 
  383    write(log_buf, 
'((A5,7x),A3,(A5,13x),1x,A6,3x,A15,3x,A15)') &
 
  384         'Step:', 
' | ', 
'Field:', 
'Iters:', &
 
  385         'Start residual:', 
'Final residual:' 
 
  388  end subroutine krylov_monitor_print_header
 
  391  subroutine krylov_monitor_print_result(this, step)
 
  392    class(ksp_monitor_t), 
intent(in) :: this
 
  393    integer, 
intent(in) :: step
 
  394    character(len=LOG_SIZE) :: log_buf
 
  395    character(len=12) :: step_str
 
  396    character(len=:), 
allocatable :: output_format
 
  398    if (this%name .eq. 
"") 
call neko_error(
'Krylov solver name is not set')
 
  401    output_format = 
'(A12,A3,A18,1x,I6,3x,E15.9,3x,E15.9)' 
  402    write(step_str, 
'(I12)') step
 
  403    step_str = adjustl(step_str)
 
  405    write(log_buf, output_format) &
 
  406         step_str, 
' | ' , adjustl(this%name), this%iter, &
 
  407         this%res_start, this%res_final
 
 
  410  end subroutine krylov_monitor_print_result
 
__device__ T solve(const T u, const T y, const T guess, const T nu, const T kappa, const T B)
 
Abstract interface for a Krylov method's constructor.
 
Abstract interface for a Krylov method's coupled solve routine.
 
Abstract interface for a Krylov method's solve routine.
 
Abstract interface for deallocating a Krylov method.
 
Defines a Matrix-vector product.
 
Identity Krylov preconditioner for accelerators.
 
Krylov preconditioner (identity)
 
Implements the base abstract type for Krylov solvers plus helper types.
 
real(kind=rp), parameter, public ksp_rel_tol
Relative tolerance.
 
real(kind=rp), parameter, public ksp_abs_tol
Absolut tolerance.
 
subroutine krylov_free(this)
Deallocate a Krylov solver.
 
integer, parameter, public ksp_max_iter
Maximum number of iters.
 
subroutine krylov_monitor_iter(this, iter, rnorm)
Monitor iteration.
 
subroutine krylov_init(this, max_iter, rel_tol, abs_tol, m, monitor)
Factory for Krylov solvers. Both creates and initializes the object.
 
subroutine krylov_monitor_print_header(this)
Print the Krylov solver's result header.
 
subroutine krylov_monitor_start(this, name)
Monitor start.
 
pure logical function krylov_is_converged(this, iter, residual)
Check for convergence.
 
subroutine krylov_set_pc(this, m)
Setup a Krylov solver's preconditioner.
 
subroutine krylov_monitor_stop(this)
Monitor stop.
 
subroutine krylov_monitor_print_result(this, step)
Print the Krylov solver's result.
 
type(log_t), public neko_log
Global log stream.
 
integer, parameter, public log_size
 
integer, parameter neko_bcknd_device
 
integer, parameter, public c_rp
 
integer, parameter, public rp
Global precision used in computations.
 
subroutine, public neko_warning(warning_msg)
Reports a warning to standard output.
 
Base type for a matrix-vector product providing .
 
A list of allocatable `bc_t`. Follows the standard interface of lists.
 
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
 
Defines a canonical Krylov preconditioner for accelerators.
 
Defines a canonical Krylov preconditioner.
 
Type for storing initial and final residuals in a Krylov solver.
 
Base abstract type for a canonical Krylov method, solving .
 
Defines a canonical Krylov preconditioner.