solve_lstsq Interface

public interface solve_lstsq

Computes the squares solution to system . (Specification)

Summary

Subroutine interface for computing least squares, i.e. the 2-norm minimizing solution.

Description

This interface provides methods for computing the least squares of a linear matrix system using a subroutine. Supported data types include real and complex. If pre-allocated work spaces are provided, no internal memory allocations take place when using this interface.

Note

The solution is based on LAPACK's singular value decomposition *GELSD methods.


Subroutines

private module subroutine stdlib_linalg_c_solve_lstsq_many(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

complex(kind=sp), intent(inout), contiguous, target :: x(:,:)

Result array/matrix x[n] or x[n,nrhs]

real(kind=sp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

complex(kind=sp), intent(inout), optional, target :: cmpl_storage(:)

[optional] complex working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=sp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop

private module subroutine stdlib_linalg_c_solve_lstsq_one(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

complex(kind=sp), intent(inout), contiguous, target :: x(:)

Result array/matrix x[n] or x[n,nrhs]

real(kind=sp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

complex(kind=sp), intent(inout), optional, target :: cmpl_storage(:)

[optional] complex working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=sp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop

private module subroutine stdlib_linalg_d_solve_lstsq_many(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

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

Result array/matrix x[n] or x[n,nrhs]

real(kind=dp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=dp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop

private module subroutine stdlib_linalg_d_solve_lstsq_one(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

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

Result array/matrix x[n] or x[n,nrhs]

real(kind=dp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=dp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop

private module subroutine stdlib_linalg_s_solve_lstsq_many(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

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

Result array/matrix x[n] or x[n,nrhs]

real(kind=sp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=sp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop

private module subroutine stdlib_linalg_s_solve_lstsq_one(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

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

Result array/matrix x[n] or x[n,nrhs]

real(kind=sp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=sp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop

private module subroutine stdlib_linalg_z_solve_lstsq_many(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

complex(kind=dp), intent(inout), contiguous, target :: x(:,:)

Result array/matrix x[n] or x[n,nrhs]

real(kind=dp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

complex(kind=dp), intent(inout), optional, target :: cmpl_storage(:)

[optional] complex working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=dp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop

private module subroutine stdlib_linalg_z_solve_lstsq_one(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(inout), target :: a(:,:)

Input matrix a[n,n]

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

Right hand side vector or array, b[n] or b[n,nrhs]

complex(kind=dp), intent(inout), contiguous, target :: x(:)

Result array/matrix x[n] or x[n,nrhs]

real(kind=dp), intent(inout), optional, target :: real_storage(:)

[optional] real working storage space

integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

[optional] integer working storage space

complex(kind=dp), intent(inout), optional, target :: cmpl_storage(:)

[optional] complex working storage space

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

[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

real(kind=dp), intent(out), optional, target :: singvals(:)

[optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

logical(kind=lk), intent(in), optional :: overwrite_a

[optional] Can A,b data be overwritten and destroyed?

integer(kind=ilp), intent(out), optional :: rank

[optional] Return rank of A

type(linalg_state_type), intent(out), optional :: err

[optional] state return flag. On error if not requested, the code will stop