stdlib_solve_cg Interface

public interface stdlib_solve_cg

Subroutines

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