stdlib_linalg_iterative_solvers Module

workspace sizes: defined by the number of vectors used by the iterative solver. version: experimental

Specifications

linop type holding the linear operator and its associated methods. The linop type is used to define the linear operator for the iterative solvers. version: experimental

Specifications

solver_workspace type holding temporal array data for the iterative solvers. version: experimental

stdlib_solve_cg_kernel interface for the conjugate gradient method. Specifications version: experimental

Specifications version: experimental

stdlib_solve_pcg_kernel interface for the preconditionned conjugate gradient method. Specifications version: experimental

stdlib_solve_bicgstab_kernel interface for the biconjugate gradient stabilized method. Specifications version: experimental

Specifications version: experimental

Specifications



Enumerations

enum, bind(c)

Enumerators

enumerator:: stdlib_size_wksp_cg = 3
enumerator:: stdlib_size_wksp_pcg = 4
enumerator:: stdlib_size_wksp_bicgstab = 8

enum, bind(c)

Enumerators

enumerator:: pc_none = 0
enumerator:: pc_jacobi = 1

Interfaces

public interface stdlib_solve_bicgstab

  • private module subroutine stdlib_solve_bicgstab_CSR_dp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    type(CSR_dp_type), intent(in) :: A
    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=dp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_dp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_dp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_bicgstab_CSR_sp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    type(CSR_sp_type), intent(in) :: A
    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=sp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_sp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_sp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_bicgstab_dense_dp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=dp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_dp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_dp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_bicgstab_dense_sp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=sp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_sp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_sp_type), intent(inout), optional, target :: workspace

    workspace for the solver

public interface stdlib_solve_bicgstab_kernel

  • private module subroutine stdlib_solve_bicgstab_kernel_dp(A, M, b, x, rtol, atol, maxiter, workspace)

    Arguments

    Type IntentOptional Attributes Name
    class(stdlib_linop_dp_type), intent(in) :: A

    linear operator

    class(stdlib_linop_dp_type), intent(in) :: M

    preconditioner linear operator

    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    real(kind=dp), intent(in) :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in) :: atol

    absolute tolerance for convergence

    integer, intent(in) :: maxiter

    maximum number of iterations

    type(stdlib_solver_workspace_dp_type), intent(inout) :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_bicgstab_kernel_sp(A, M, b, x, rtol, atol, maxiter, workspace)

    Arguments

    Type IntentOptional Attributes Name
    class(stdlib_linop_sp_type), intent(in) :: A

    linear operator

    class(stdlib_linop_sp_type), intent(in) :: M

    preconditioner linear operator

    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    real(kind=sp), intent(in) :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in) :: atol

    absolute tolerance for convergence

    integer, intent(in) :: maxiter

    maximum number of iterations

    type(stdlib_solver_workspace_sp_type), intent(inout) :: workspace

    workspace for the solver

public interface stdlib_solve_cg

  • private module subroutine stdlib_solve_cg_CSR_dp(A, b, x, di, rtol, atol, maxiter, restart, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    type(CSR_dp_type), intent(in) :: A
    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=dp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    type(stdlib_solver_workspace_dp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_cg_CSR_sp(A, b, x, di, rtol, atol, maxiter, restart, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    type(CSR_sp_type), intent(in) :: A
    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=sp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    type(stdlib_solver_workspace_sp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_cg_dense_dp(A, b, x, di, rtol, atol, maxiter, restart, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=dp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    type(stdlib_solver_workspace_dp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_cg_dense_sp(A, b, x, di, rtol, atol, maxiter, restart, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=sp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    type(stdlib_solver_workspace_sp_type), intent(inout), optional, target :: workspace

    workspace for the solver

public interface stdlib_solve_cg_kernel

  • private module subroutine stdlib_solve_cg_kernel_dp(A, b, x, rtol, atol, maxiter, workspace)

    Arguments

    Type IntentOptional Attributes Name
    class(stdlib_linop_dp_type), intent(in) :: A

    linear operator

    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    real(kind=dp), intent(in) :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in) :: atol

    absolut tolerance for convergence

    integer, intent(in) :: maxiter

    maximum number of iterations

    type(stdlib_solver_workspace_dp_type), intent(inout) :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_cg_kernel_sp(A, b, x, rtol, atol, maxiter, workspace)

    Arguments

    Type IntentOptional Attributes Name
    class(stdlib_linop_sp_type), intent(in) :: A

    linear operator

    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    real(kind=sp), intent(in) :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in) :: atol

    absolut tolerance for convergence

    integer, intent(in) :: maxiter

    maximum number of iterations

    type(stdlib_solver_workspace_sp_type), intent(inout) :: workspace

    workspace for the solver

public interface stdlib_solve_pcg

  • private module subroutine stdlib_solve_pcg_CSR_dp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    type(CSR_dp_type), intent(in) :: A
    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=dp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_dp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_dp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_pcg_CSR_sp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    type(CSR_sp_type), intent(in) :: A
    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=sp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_sp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_sp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_pcg_dense_dp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=dp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_dp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_dp_type), intent(inout), optional, target :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_pcg_dense_sp(A, b, x, di, rtol, atol, maxiter, restart, precond, M, workspace)

    linear operator matrix

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    logical(kind=int8), intent(in), optional, target :: di(:)

    dirichlet conditions mask

    real(kind=sp), intent(in), optional :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in), optional :: atol

    absolute tolerance for convergence

    integer, intent(in), optional :: maxiter

    maximum number of iterations

    logical, intent(in), optional :: restart

    restart flag

    integer, intent(in), optional :: precond

    preconditioner method enumerator

    class(stdlib_linop_sp_type), intent(in), optional, target :: M

    preconditioner linear operator

    type(stdlib_solver_workspace_sp_type), intent(inout), optional, target :: workspace

    workspace for the solver

public interface stdlib_solve_pcg_kernel

  • private module subroutine stdlib_solve_pcg_kernel_dp(A, M, b, x, rtol, atol, maxiter, workspace)

    Arguments

    Type IntentOptional Attributes Name
    class(stdlib_linop_dp_type), intent(in) :: A

    linear operator

    class(stdlib_linop_dp_type), intent(in) :: M

    preconditioner linear operator

    real(kind=dp), intent(in) :: b(:)

    right-hand side vector

    real(kind=dp), intent(inout) :: x(:)

    solution vector and initial guess

    real(kind=dp), intent(in) :: rtol

    relative tolerance for convergence

    real(kind=dp), intent(in) :: atol

    absolute tolerance for convergence

    integer, intent(in) :: maxiter

    maximum number of iterations

    type(stdlib_solver_workspace_dp_type), intent(inout) :: workspace

    workspace for the solver

  • private module subroutine stdlib_solve_pcg_kernel_sp(A, M, b, x, rtol, atol, maxiter, workspace)

    Arguments

    Type IntentOptional Attributes Name
    class(stdlib_linop_sp_type), intent(in) :: A

    linear operator

    class(stdlib_linop_sp_type), intent(in) :: M

    preconditioner linear operator

    real(kind=sp), intent(in) :: b(:)

    right-hand side vector

    real(kind=sp), intent(inout) :: x(:)

    solution vector and initial guess

    real(kind=sp), intent(in) :: rtol

    relative tolerance for convergence

    real(kind=sp), intent(in) :: atol

    absolute tolerance for convergence

    integer, intent(in) :: maxiter

    maximum number of iterations

    type(stdlib_solver_workspace_sp_type), intent(inout) :: workspace

    workspace for the solver


Derived Types

type, public ::  stdlib_linop_dp_type

Components

Type Visibility Attributes Name Initial
procedure(reduction_sub_dp), public, nopass, pointer :: inner_product => default_dot_dp
procedure(vector_sub_dp), public, nopass, pointer :: matvec => null()

type, public ::  stdlib_linop_sp_type

Components

Type Visibility Attributes Name Initial
procedure(reduction_sub_sp), public, nopass, pointer :: inner_product => default_dot_sp
procedure(vector_sub_sp), public, nopass, pointer :: matvec => null()

type, public ::  stdlib_solver_workspace_dp_type

Components

Type Visibility Attributes Name Initial
procedure(logger_sub_dp), public, pointer, nopass :: callback => null()
real(kind=dp), public, allocatable :: tmp(:,:)

type, public ::  stdlib_solver_workspace_sp_type

Components

Type Visibility Attributes Name Initial
procedure(logger_sub_sp), public, pointer, nopass :: callback => null()
real(kind=sp), public, allocatable :: tmp(:,:)