Provides a support for various linear algebra procedures (Specification)
Computes the Cholesky factorization , or . (Specification)
Pure function interface for computing the Cholesky triangular factors.
This interface provides methods for computing the lower- or upper- triangular matrix from the
Cholesky factorization of a real
symmetric or complex
Hermitian matrix.
Supported data types include real
and complex
.
Note
The solution is based on LAPACK's *POTRF
methods.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[m,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
Output matrix with Cholesky factors c[n,n]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[m,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
Output matrix with Cholesky factors c[n,n]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[m,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
Output matrix with Cholesky factors c[n,n]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[m,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
Output matrix with Cholesky factors c[n,n]
Computes the Cholesky factorization , or . (Specification)
Pure subroutine interface for computing the Cholesky triangular factors.
This interface provides methods for computing the lower- or upper- triangular matrix from the
Cholesky factorization of a real
symmetric or complex
Hermitian matrix.
Supported data types include real
and complex
.
The factorization is computed in-place if only one matrix argument is present; or returned into
a second matrix argument, if present. The lower
logical
flag allows to select between upper or
lower factorization; the other_zeroed
optional logical
flag allows to choose whether the unused
part of the triangular matrix should be filled with zeroes.
Note
The solution is based on LAPACK's *POTRF
methods.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
complex(kind=sp), | intent(out) | :: | c(:,:) |
Output matrix with Cholesky factors c[n,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
real(kind=dp), | intent(out) | :: | c(:,:) |
Output matrix with Cholesky factors c[n,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
real(kind=sp), | intent(out) | :: | c(:,:) |
Output matrix with Cholesky factors c[n,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
complex(kind=dp), | intent(out) | :: | c(:,:) |
Output matrix with Cholesky factors c[n,n] |
||
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | lower |
[optional] is the lower or upper triangular factor required? Default = lower |
|
logical(kind=lk), | intent(in), | optional | :: | other_zeroed |
[optional] should the unused half of the return matrix be zeroed out? Default: yes |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Computes the cross product of two vectors, returning a rank-1 and size-3 array (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(3) | |||
complex(kind=dp), | intent(in) | :: | b(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(3) | |||
complex(kind=sp), | intent(in) | :: | b(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | a(3) | |||
integer(kind=int16), | intent(in) | :: | b(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | a(3) | |||
integer(kind=int32), | intent(in) | :: | b(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | a(3) | |||
integer(kind=int64), | intent(in) | :: | b(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | a(3) | |||
integer(kind=int8), | intent(in) | :: | b(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(3) | |||
real(kind=dp), | intent(in) | :: | b(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(3) | |||
real(kind=sp), | intent(in) | :: | b(3) |
Computes the determinant of a square matrix (Specification)
Interface for computing matrix determinant.
This interface provides methods for computing the determinant of a matrix.
Supported data types include real
and complex
.
Note
The provided functions are intended for square matrices only.
Note
BLAS/LAPACK backends do not currently support extended precision (xdp
).
real(sp) :: a(3,3), d
type(linalg_state_type) :: state
a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
! ...
d = det(a,err=state)
if (state%ok()) then
print *, 'Success! det=',d
else
print *, state%print()
endif
! ...
Creates a diagonal array or extract the diagonal elements of an array (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | v(:) | |||
integer, | intent(in) | :: | k |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) | |||
integer, | intent(in) | :: | k |
Solves the eigendecomposition for square matrix . (Specification)
Subroutine interface for computing eigenvalues and eigenvectors of a square matrix.
This interface provides methods for computing the eigenvalues, and optionally eigenvectors,
of a general square matrix. Supported data types include real
and complex
, and no assumption is
made on the matrix structure. The user may request either left, right, or both
eigenvectors to be returned. They are returned as columns of a square matrix with the same size as A
.
Preallocated space for both eigenvalues lambda
and the eigenvector matrices must be user-provided.
Note
The solution is based on LAPACK's general eigenproblem solvers *GEEV
.
Note
BLAS/LAPACK backends do not currently support extended precision (xdp
).
Eigendecomposition of matrix A returning an array lambda
of eigenvalues,
and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
complex(kind=sp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
complex(kind=sp), | intent(out), | optional, | target | :: | right(:,:) |
The columns of RIGHT contain the right eigenvectors of A |
complex(kind=sp), | intent(out), | optional, | target | :: | left(:,:) |
The columns of LEFT contain the left eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of matrix A returning an array lambda
of eigenvalues,
and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
complex(kind=dp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
complex(kind=dp), | intent(out), | optional, | target | :: | right(:,:) |
The columns of RIGHT contain the right eigenvectors of A |
complex(kind=dp), | intent(out), | optional, | target | :: | left(:,:) |
The columns of LEFT contain the left eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of matrix A returning an array lambda
of eigenvalues,
and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
complex(kind=sp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
complex(kind=sp), | intent(out), | optional, | target | :: | right(:,:) |
The columns of RIGHT contain the right eigenvectors of A |
complex(kind=sp), | intent(out), | optional, | target | :: | left(:,:) |
The columns of LEFT contain the left eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of matrix A returning an array lambda
of eigenvalues,
and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
complex(kind=dp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
complex(kind=dp), | intent(out), | optional, | target | :: | right(:,:) |
The columns of RIGHT contain the right eigenvectors of A |
complex(kind=dp), | intent(out), | optional, | target | :: | left(:,:) |
The columns of LEFT contain the left eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of matrix A returning an array lambda
of real eigenvalues,
and optionally right or left eigenvectors. Returns an error if the eigenvalues had
non-trivial imaginary parts.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=dp), | intent(out) | :: | lambda(:) |
Array of real eigenvalues |
||
complex(kind=dp), | intent(out), | optional, | target | :: | right(:,:) |
The columns of RIGHT contain the right eigenvectors of A |
complex(kind=dp), | intent(out), | optional, | target | :: | left(:,:) |
The columns of LEFT contain the left eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of matrix A returning an array lambda
of real eigenvalues,
and optionally right or left eigenvectors. Returns an error if the eigenvalues had
non-trivial imaginary parts.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=sp), | intent(out) | :: | lambda(:) |
Array of real eigenvalues |
||
complex(kind=sp), | intent(out), | optional, | target | :: | right(:,:) |
The columns of RIGHT contain the right eigenvectors of A |
complex(kind=sp), | intent(out), | optional, | target | :: | left(:,:) |
The columns of LEFT contain the left eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Solves the eigendecomposition for a real symmetric or complex Hermitian square matrix. (Specification)
Subroutine interface for computing eigenvalues and eigenvectors of a real symmetric or complex Hermitian square matrix.
This interface provides methods for computing the eigenvalues, and optionally eigenvectors,
of a real symmetric or complex Hermitian square matrix. Supported data types include real
and complex
.
The matrix must be symmetric (if real
) or Hermitian (if complex
). Only the lower or upper
half of the matrix is accessed, and the user can select which using the optional upper_a
flag (default: use lower half). The vectors are orthogonal, and may be returned as columns of an optional
matrix vectors
with the same kind and size as A
.
Preallocated space for both eigenvalues lambda
and the eigenvector matrix must be user-provided.
Note
The solution is based on LAPACK's eigenproblem solvers *SYEV
/*HEEV
.
Note
BLAS/LAPACK backends do not currently support extended precision (xdp
).
Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda
of eigenvalues, and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=sp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
complex(kind=sp), | intent(out), | optional, | target | :: | vectors(:,:) |
The columns of vectors contain the orthonormal eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda
of eigenvalues, and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=dp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
real(kind=dp), | intent(out), | optional, | target | :: | vectors(:,:) |
The columns of vectors contain the orthonormal eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda
of eigenvalues, and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=sp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
real(kind=sp), | intent(out), | optional, | target | :: | vectors(:,:) |
The columns of vectors contain the orthonormal eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda
of eigenvalues, and optionally right or left eigenvectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=dp), | intent(out) | :: | lambda(:) |
Array of eigenvalues |
||
complex(kind=dp), | intent(out), | optional, | target | :: | vectors(:,:) |
The columns of vectors contain the orthonormal eigenvectors of A |
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Returns the eigenvalues , , for square matrix . (Specification)
Function interface for computing the eigenvalues of a square matrix.
This interface provides functions for returning the eigenvalues of a general square matrix.
Supported data types include real
and complex
, and no assumption is made on the matrix structure.
An error stop
is thrown in case of failure; otherwise, error information can be returned
as an optional type(linalg_state_type)
output flag.
Note
The solution is based on LAPACK's general eigenproblem solvers *GEEV
.
Note
BLAS/LAPACK backends do not currently support extended precision (xdp
).
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
Array of singular values
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
Array of singular values
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
Array of singular values
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
Array of singular values
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Return an array of eigenvalues of matrix A.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Returns the eigenvalues , , for a real symmetric or complex Hermitian square matrix. (Specification)
Function interface for computing the eigenvalues of a real symmetric or complex hermitian square matrix.
This interface provides functions for returning the eigenvalues of a real symmetric or complex Hermitian
square matrix. Supported data types include real
and complex
. The matrix must be symmetric
(if real
) or Hermitian (if complex
). Only the lower or upper half of the matrix is accessed,
and the user can select which using the optional upper_a
flag (default: use lower half).
An error stop
is thrown in case of failure; otherwise, error information can be returned
as an optional type(linalg_state_type)
output flag.
Note
The solution is based on LAPACK's eigenproblem solvers *SYEV
/*HEEV
.
Note
BLAS/LAPACK backends do not currently support extended precision (xdp
).
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
Array of singular values
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
Array of singular values
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
Array of singular values
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
Array of singular values
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Return an array of eigenvalues of real symmetric / complex hermitian A
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
logical(kind=lk), | intent(in), | optional | :: | upper_a |
[optional] Should the upper/lower half of A be used? Default: lower |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Vector norm: subroutine interface version: experimental
Computes the vector norm of a generic-rank array . (Specification)
Subroutine interface that returns one of several scalar norm metrics of a real
or complex
input array , that can have any rank. For generic rank-n arrays, the scalar norm over
the whole array is returned by default. If n>=2
and the optional input dimension dim
is
specified, a rank n-1
array is returned with dimension dim
collapsed, containing all 1D
array norms evaluated along dimension dim
only.
This pure subroutine
interface provides methods for computing the vector norm(s) of an array.
Supported data types include real
and complex
.
Input arrays may have generic rank from 1 to 3.
Norm type input is mandatory, and it is provided via the order
argument.
This can be provided as either an integer
value or a character
string.
Allowed metrics are:
- 1-norm : order
= 1 or '1'
- Euclidean norm : order
= 2 or '2'
- p-norm : integer
order
, order>=3
- Infinity norm : order = huge(0) or 'inf'
- Minus-infinity norm : order = -huge(0) or '-inf'
real(sp) :: a(3,3), na, rown(3)
type(linalg_state_type) :: err
a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
! L2 norm: whole matrix
call get_norm(a, na, 2)
! Infinity norms of each row, with error control
call get_norm(a, rown, 'inf', dim=2, err=err)
Scalar norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Scalar norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Scalar norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Scalar norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Scalar norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Scalar norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Scalar norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Scalar norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:) |
Input 1-d matrix a(:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input 2-d matrix a(:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=sp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
|
real(kind=dp), | intent(out) | :: | nrm |
Norm of the matrix. |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=sp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:,:) |
Input matrix a[..] |
||
real(kind=dp), | intent(out) | :: | nrm(merge(size(a,1),size(a,2),mask=1
|
Norm of the matrix. (Same shape as | ||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Inverse of a square matrix (Specification)
This interface provides methods for computing the inverse of a square real
or complex
matrix.
The inverse is defined such that .
This function interface provides methods that return the inverse of a square matrix.
Supported data types include real
and complex
.
The inverse matrix is returned as a function result.
Exceptions are raised in case of singular matrix or invalid size, and trigger an error stop
if
the state flag err
is not provided.
Note
The provided functions are intended for square matrices.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Output matrix inverse
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Output matrix inverse
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Output matrix inverse
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Output matrix inverse
Inversion of a square matrix (Specification)
This interface provides methods for inverting a square real
or complex
matrix in-place.
The inverse is defined such that .
This subroutine interface provides a way to compute the inverse of a matrix.
Supported data types include real
and complex
.
The user may provide a unique matrix argument a
. In this case, a
is replaced by the inverse matrix.
on output. Otherwise, one may provide two separate arguments: an input matrix a
and an output matrix
inva
. In this case, a
will not be modified, and the inverse is returned in inva
.
Pre-allocated storage may be provided for the array of pivot indices, pivot
. If all pre-allocated
work spaces are provided, no internal memory allocations take place when using this interface.
Note
The provided subroutines are intended for square matrices.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(inout) | :: | a(:,:) |
Input matrix a[n,n] |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(inout) | :: | a(:,:) |
Input matrix a[n,n] |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(inout) | :: | a(:,:) |
Input matrix a[n,n] |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(inout) | :: | a(:,:) |
Input matrix a[n,n] |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n]. |
||
complex(kind=sp), | intent(out) | :: | inva(:,:) |
Inverse matrix a[n,n]. |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n]. |
||
real(kind=dp), | intent(out) | :: | inva(:,:) |
Inverse matrix a[n,n]. |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n]. |
||
real(kind=sp), | intent(out) | :: | inva(:,:) |
Inverse matrix a[n,n]. |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n]. |
||
complex(kind=dp), | intent(out) | :: | inva(:,:) |
Inverse matrix a[n,n]. |
||
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Checks if a matrix (rank-2 array) is diagonal (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) |
Checks if a matrix (rank-2 array) is Hermitian (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) |
Checks if a matrix (rank-2 array) is Hessenberg (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Checks if a matrix (rank-2 array) is skew-symmetric (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) |
Checks if a matrix (rank-2 array) is square (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) |
Checks if a matrix (rank-2 array) is symmetric (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) |
Checks if a matrix (rank-2 array) is triangular (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) | |||
character(len=1), | intent(in) | :: | uplo |
Computes the Kronecker product of two arrays of size M1xN1, and of M2xN2, returning an (M1M2)x(N1N2) array (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) | |||
complex(kind=dp), | intent(in) | :: | B(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) | |||
complex(kind=sp), | intent(in) | :: | B(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) | |||
integer(kind=int16), | intent(in) | :: | B(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) | |||
integer(kind=int32), | intent(in) | :: | B(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) | |||
integer(kind=int64), | intent(in) | :: | B(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) | |||
integer(kind=int8), | intent(in) | :: | B(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) | |||
real(kind=dp), | intent(in) | :: | B(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) | |||
real(kind=sp), | intent(in) | :: | B(:,:) |
Computes the squares solution to system . (Specification)
Interface for computing least squares, i.e. the 2-norm minimizing solution.
This interface provides methods for computing the least squares of a linear matrix system.
Supported data types include real
and complex
.
Note
The solution is based on LAPACK's singular value decomposition *GELSD
methods.
Type | Intent | Optional | 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] |
||
real(kind=sp), | intent(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
real(kind=sp), | intent(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
real(kind=dp), | intent(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
real(kind=dp), | intent(in), | optional | :: | cond |
[optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0. |
|
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 |
Result array/matrix x[n] or x[n,nrhs]
Computes the integer, real [, complex] working space required by the least-squares solver (Specification)
This interface provides sizes of integer, real [, complex] working spaces required by the least-squares solver. These sizes can be used to pre-allocated working arrays in case several repeated least-squares solutions to a same system are sought. If pre-allocated working arrays are provided, no internal allocations will take place.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
complex(kind=sp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | lcwork |
Size of the working space arrays |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
complex(kind=sp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | lcwork |
Size of the working space arrays |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
real(kind=dp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
real(kind=dp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
real(kind=sp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
real(kind=sp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
complex(kind=dp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | lcwork |
Size of the working space arrays |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
complex(kind=dp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
||
integer(kind=ilp), | intent(out) | :: | lrwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | liwork |
Size of the working space arrays |
||
integer(kind=ilp), | intent(out) | :: | lcwork |
Size of the working space arrays |
Computes the vector norm of a generic-rank array . (Specification)
Return one of several scalar norm metrics of a real
or complex
input array ,
that can have any rank. For generic rank-n arrays, the scalar norm over the whole
array is returned by default. If n>=2
and the optional input dimension dim
is specified,
a rank n-1
array is returned with dimension dim
collapsed, containing all 1D array norms
evaluated along dimension dim
only.
This interface provides methods for computing the vector norm(s) of an array.
Supported data types include real
and complex
.
Input arrays may have generic rank from 1 to 3.
Norm type input is mandatory, and it is provided via the order
argument.
This can be provided as either an integer
value or a character
string.
Allowed metrics are:
- 1-norm : order
= 1 or '1'
- Euclidean norm : order
= 2 or '2'
- p-norm : integer
order
, order>=3
- Infinity norm : order = huge(0) or 'inf'
- Minus-infinity norm : order = -huge(0) or '-inf'
real(sp) :: a(3,3), na, rown(3)
a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
! L2 norm: whole matrix
na = norm(a, 2)
! Infinity norm of each row
rown = norm(a, 'inf', dim=2)
Scalar norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Scalar norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Scalar norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Scalar norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Scalar norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Scalar norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Scalar norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Scalar norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:) |
Input 1-d matrix a(:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input 2-d matrix a(:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Array norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Array norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Array norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Array norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Array norms: complex(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Array norms: real(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Array norms: real(sp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Array norms: complex(dp)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:,:) |
Input 3-d matrix a(:,:,:) |
||
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
Norm of the matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
character(len=*), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
||
type(linalg_state_type), | intent(out) | :: | err |
Output state return flag. |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:,:) |
Input matrix a[..] |
|
integer(kind=ilp), | intent(in) | :: | order |
Order of the matrix norm being computed. |
||
integer(kind=ilp), | intent(in) | :: | dim |
Dimension the norm is computed along |
Norm of the matrix. (Same shape as a
, with dim
dropped).
Determinant operator of a square matrix (Specification)
Pure operator interface for computing matrix determinant.
This pure operator interface provides a convenient way to compute the determinant of a matrix. Supported data types include real and complex.
Note
The provided functions are intended for square matrices.
Note
BLAS/LAPACK backends do not currently support extended precision (xdp
).
! ...
real(sp) :: matrix(3,3), d
matrix = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
d = .det.matrix
! ...
Inverse operator of a square matrix (Specification)
Operator interface for computing the inverse of a square real
or complex
matrix.
This operator interface provides a convenient way to compute the inverse of a matrix.
Supported data types include real
and complex
. On input errors or singular matrix,
NaNs will be returned.
Note
The provided functions are intended for square matrices.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
Result matrix
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
Result matrix
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
Result matrix
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
Result matrix
Computes the outer product of two vectors, returning a rank-2 array (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | u(:) | |||
complex(kind=dp), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | u(:) | |||
complex(kind=sp), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | u(:) | |||
integer(kind=int16), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | u(:) | |||
integer(kind=int32), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | u(:) | |||
integer(kind=int64), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | u(:) | |||
integer(kind=int8), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | u(:) | |||
real(kind=dp), | intent(in) | :: | v(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | u(:) | |||
real(kind=sp), | intent(in) | :: | v(:) |
Computes the QR factorization of matrix . (Specification)
Compute the QR factorization of a real
or complex
matrix: , where is orthonormal
and is upper-triangular. Matrix has size [m,n]
, with .
This interface provides methods for computing the QR factorization of a matrix.
Supported data types include real
and complex
. If a pre-allocated work space
is provided, no internal memory allocations take place when using this interface.
Given k = min(m,n)
, one can write \cdot ).
The user may want the full problem (provide shape(Q)==[m,m]
, shape(R)==[m,n]
) or the reduced
problem only: (provide shape(Q)==[m,k]
, shape(R)==[k,n]
).
Note
The solution is based on LAPACK's QR factorization (*GEQRF
) and ordered matrix output (*ORGQR
, *UNGQR
).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
complex(kind=sp), | intent(out), | contiguous, target | :: | q(:,:) |
Orthogonal matrix Q ([m,m], or [m,k] if reduced) |
|
complex(kind=sp), | intent(out), | contiguous, target | :: | r(:,:) |
Upper triangular matrix R ([m,n], or [k,n] if reduced) |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
complex(kind=sp), | intent(out), | optional, | target | :: | storage(:) |
[optional] Provide pre-allocated workspace, size to be checked with qr_space |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
real(kind=dp), | intent(out), | contiguous, target | :: | q(:,:) |
Orthogonal matrix Q ([m,m], or [m,k] if reduced) |
|
real(kind=dp), | intent(out), | contiguous, target | :: | r(:,:) |
Upper triangular matrix R ([m,n], or [k,n] if reduced) |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
real(kind=dp), | intent(out), | optional, | target | :: | storage(:) |
[optional] Provide pre-allocated workspace, size to be checked with qr_space |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
real(kind=sp), | intent(out), | contiguous, target | :: | q(:,:) |
Orthogonal matrix Q ([m,m], or [m,k] if reduced) |
|
real(kind=sp), | intent(out), | contiguous, target | :: | r(:,:) |
Upper triangular matrix R ([m,n], or [k,n] if reduced) |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
real(kind=sp), | intent(out), | optional, | target | :: | storage(:) |
[optional] Provide pre-allocated workspace, size to be checked with qr_space |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
complex(kind=dp), | intent(out), | contiguous, target | :: | q(:,:) |
Orthogonal matrix Q ([m,m], or [m,k] if reduced) |
|
complex(kind=dp), | intent(out), | contiguous, target | :: | r(:,:) |
Upper triangular matrix R ([m,n], or [k,n] if reduced) |
|
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
complex(kind=dp), | intent(out), | optional, | target | :: | storage(:) |
[optional] Provide pre-allocated workspace, size to be checked with qr_space |
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Computes the working array space required by the QR factorization solver (Specification)
This interface returns the size of the real
or complex
working storage required by the
QR factorization solver. The working size only depends on the kind (real
or complex
) and size of
the matrix being factorized. Storage size can be used to pre-allocate a working array in case several
repeated QR factorizations to a same-size matrix are sought. If pre-allocated working arrays
are provided, no internal allocations will take place during the factorization.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
integer(kind=ilp), | intent(out) | :: | lwork |
Minimum workspace size for both operations |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
State return flag. Returns an error if the query failed |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
integer(kind=ilp), | intent(out) | :: | lwork |
Minimum workspace size for both operations |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
State return flag. Returns an error if the query failed |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
integer(kind=ilp), | intent(out) | :: | lwork |
Minimum workspace size for both operations |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
State return flag. Returns an error if the query failed |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix a[m,n] |
|
integer(kind=ilp), | intent(out) | :: | lwork |
Minimum workspace size for both operations |
||
type(linalg_state_type), | intent(out), | optional | :: | err |
State return flag. Returns an error if the query failed |
Solves the linear system for the unknown vector from a square matrix . (Specification)
Interface for solving a linear system arising from a general matrix.
This interface provides methods for computing the solution of a linear matrix system.
Supported data types include real
and complex
. No assumption is made on the matrix
structure.
The function can solve simultaneously either one (from a 1-d right-hand-side vector b(:)
)
or several (from a 2-d right-hand-side vector b(:,:)
) systems.
Note
The solution is based on LAPACK's generic LU decomposition based solvers *GESV
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
complex(kind=sp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
complex(kind=sp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
real(kind=dp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
real(kind=dp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
real(kind=sp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
real(kind=sp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
complex(kind=dp), | intent(in) | :: | b(:,:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | a(:,:) |
Input matrix a[n,n] |
||
complex(kind=dp), | intent(in) | :: | b(:) |
Right hand side vector or array, b[n] or b[n,nrhs] |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Type | Intent | Optional | 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] |
||
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out) | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Result array/matrix x[n] or x[n,nrhs]
Computes the squares solution to system . (Specification)
Subroutine interface for computing least squares, i.e. the 2-norm minimizing solution.
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.
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Solves the linear system for the unknown vector from a square matrix . (Specification)
Subroutine interface for solving a linear system using LU decomposition.
This interface provides methods for computing the solution of a linear matrix system using
a subroutine. Supported data types include real
and complex
. No assumption is made on the matrix
structure. Preallocated space for the solution vector x
is user-provided, and it may be provided
for the array of pivot indices, pivot
. If all pre-allocated work spaces are provided, no internal
memory allocations take place when using this interface.
The function can solve simultaneously either one (from a 1-d right-hand-side vector b(:)
)
or several (from a 2-d right-hand-side vector b(:,:)
) systems.
Note
The solution is based on LAPACK's generic LU decomposition based solvers *GESV
.
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Type | Intent | Optional | 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] |
|
integer(kind=ilp), | intent(inout), | optional, | target | :: | pivot(:) |
[optional] Storage array for the diagonal pivot indices |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Computes the singular value decomposition of a real
or complex
2d matrix.
(Specification)
Interface for computing the singular value decomposition of a real
or complex
2d matrix.
This interface provides methods for computing the singular value decomposition of a matrix.
Supported data types include real
and complex
. The subroutine returns a real
array of
singular values, and optionally, left- and right- singular vector matrices, U
and V
.
For a matrix A
with size [m,n], full matrix storage for U
and V
should be [m,m] and [n,n].
It is possible to use partial storage [m,k] and [k,n], k=min(m,n)
, choosing full_matrices=.false.
.
Note
The solution is based on LAPACK's singular value decomposition *GESDD
methods.
real(sp) :: a(2,3), s(2), u(2,2), vt(3,3)
a = reshape([3,2, 2,3, 2,-2],[2,3])
call svd(A,s,u,v)
print *, 'singular values = ',s
Compute singular value decomposition of a matrix
This function computes the singular value decomposition of a real
or complex
matrix ,
and returns the array of singular values, and optionally the left matrix containing the
left unitary singular vectors, and the right matrix , containing the right unitary
singular vectors.
param: a Input matrix of size [m,n].
param: s Output real
array of size [min(m,n)] returning a list of singular values.
param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns.
param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten.
param: full_matrices [optional] If .true.
(default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n)
.
param: err [optional] State return flag.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=sp), | intent(out) | :: | s(:) |
Array of singular values |
||
complex(kind=sp), | intent(out), | optional, | target | :: | u(:,:) |
The columns of U contain the left singular vectors |
complex(kind=sp), | intent(out), | optional, | target | :: | vt(:,:) |
The rows of V^T contain the right singular vectors |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
logical(kind=lk), | intent(in), | optional | :: | full_matrices |
[optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n) |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Compute singular value decomposition of a matrix
This function computes the singular value decomposition of a real
or complex
matrix ,
and returns the array of singular values, and optionally the left matrix containing the
left unitary singular vectors, and the right matrix , containing the right unitary
singular vectors.
param: a Input matrix of size [m,n].
param: s Output real
array of size [min(m,n)] returning a list of singular values.
param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns.
param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten.
param: full_matrices [optional] If .true.
(default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n)
.
param: err [optional] State return flag.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=dp), | intent(out) | :: | s(:) |
Array of singular values |
||
real(kind=dp), | intent(out), | optional, | target | :: | u(:,:) |
The columns of U contain the left singular vectors |
real(kind=dp), | intent(out), | optional, | target | :: | vt(:,:) |
The rows of V^T contain the right singular vectors |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
logical(kind=lk), | intent(in), | optional | :: | full_matrices |
[optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n) |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Compute singular value decomposition of a matrix
This function computes the singular value decomposition of a real
or complex
matrix ,
and returns the array of singular values, and optionally the left matrix containing the
left unitary singular vectors, and the right matrix , containing the right unitary
singular vectors.
param: a Input matrix of size [m,n].
param: s Output real
array of size [min(m,n)] returning a list of singular values.
param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns.
param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten.
param: full_matrices [optional] If .true.
(default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n)
.
param: err [optional] State return flag.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=sp), | intent(out) | :: | s(:) |
Array of singular values |
||
real(kind=sp), | intent(out), | optional, | target | :: | u(:,:) |
The columns of U contain the left singular vectors |
real(kind=sp), | intent(out), | optional, | target | :: | vt(:,:) |
The rows of V^T contain the right singular vectors |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
logical(kind=lk), | intent(in), | optional | :: | full_matrices |
[optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n) |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Compute singular value decomposition of a matrix
This function computes the singular value decomposition of a real
or complex
matrix ,
and returns the array of singular values, and optionally the left matrix containing the
left unitary singular vectors, and the right matrix , containing the right unitary
singular vectors.
param: a Input matrix of size [m,n].
param: s Output real
array of size [min(m,n)] returning a list of singular values.
param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns.
param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten.
param: full_matrices [optional] If .true.
(default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n)
.
param: err [optional] State return flag.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(inout), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
real(kind=dp), | intent(out) | :: | s(:) |
Array of singular values |
||
complex(kind=dp), | intent(out), | optional, | target | :: | u(:,:) |
The columns of U contain the left singular vectors |
complex(kind=dp), | intent(out), | optional, | target | :: | vt(:,:) |
The rows of V^T contain the right singular vectors |
logical(kind=lk), | intent(in), | optional | :: | overwrite_a |
[optional] Can A data be overwritten and destroyed? |
|
logical(kind=lk), | intent(in), | optional | :: | full_matrices |
[optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n) |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Computes the singular values of a real
or complex
2d matrix.
(Specification)
Function interface for computing the array of singular values from the singular value decomposition
of a real
or complex
2d matrix.
This interface provides methods for computing the singular values a 2d matrix.
Supported data types include real
and complex
. The function returns a real
array of
singular values, with size [min(m,n)].
Note
The solution is based on LAPACK's singular value decomposition *GESDD
methods.
real(sp) :: a(2,3), s(2)
a = reshape([3,2, 2,3, 2,-2],[2,3])
s = svdvals(A)
print *, 'singular values = ',s
Compute singular values from the singular-value decomposition of a matrix .
This function returns the array of singular values from the singular value decomposition of a real
or complex
matrix .
param: a Input matrix of size [m,n]. param: err [optional] State return flag.
param: s real
array of size [min(m,n)] returning a list of singular values.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Compute singular values from the singular-value decomposition of a matrix .
This function returns the array of singular values from the singular value decomposition of a real
or complex
matrix .
param: a Input matrix of size [m,n]. param: err [optional] State return flag.
param: s real
array of size [min(m,n)] returning a list of singular values.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Compute singular values from the singular-value decomposition of a matrix .
This function returns the array of singular values from the singular value decomposition of a real
or complex
matrix .
param: a Input matrix of size [m,n]. param: err [optional] State return flag.
param: s real
array of size [min(m,n)] returning a list of singular values.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Compute singular values from the singular-value decomposition of a matrix .
This function returns the array of singular values from the singular value decomposition of a real
or complex
matrix .
param: a Input matrix of size [m,n]. param: err [optional] State return flag.
param: s real
array of size [min(m,n)] returning a list of singular values.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in), | target | :: | a(:,:) |
Input matrix A[m,n] |
|
type(linalg_state_type), | intent(out), | optional | :: | err |
[optional] state return flag. On error if not requested, the code will stop |
Array of singular values
Computes the trace of a matrix (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=dp), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int8), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int16), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int32), | intent(in) | :: | A(:,:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=int64), | intent(in) | :: | A(:,:) |
Constructs the identity matrix. (Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | dim1 | |||
integer, | intent(in), | optional | :: | dim2 |