mnorm Interface

public interface mnorm

Matrix norms: function interface version: experimental

Computes the matrix norm of a generic-rank array . (Specification)

Summary

Return one of several matrix norm metrics of a real or complex input array , that can have rank 2 or higher. For rank-2 arrays, the matrix norm is returned. If rank>2 and the optional input dimensions dim are specified, a rank n-2 array is returned with dimensions dim(1),dim(2) collapsed, containing all matrix norms evaluated over the specified dimensions only. dim==[1,2] are assumed as default dimensions if not specified.

Description

This interface provides methods for computing the matrix norm(s) of an array.
Supported data types include real and complex. Input arrays must have rank >= 2.

Norm type input is optional, 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'
- 2-norm: order = 2 or '2' - Euclidean/Frobenius: order = 'Euclidean','Frobenius', or argument not specified - Infinity norm: order = huge(0) or 'Inf'

If an invalid norm type is provided, the routine returns an error state.

Example

    real(sp) :: a(3,3), na
    real(sp) :: b(3,3,4), nb(4)  ! Array of 4 3x3 matrices
    a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])

    ! Euclidean/Frobenius norm of single matrix
    na = mnorm(a)
    na = mnorm(a, 'Euclidean')

    ! 1-norm of each 3x3 matrix in b
    nb = mnorm(b, 1, dim=[1,2])

    ! Infinity-norm 
    na = mnorm(b, 'inf', dim=[3,2])

Functions

private module function matrix_norm_3D_to_1D_char_c(a, order, dim, err) result(nrm)

Matrix norms: complex(sp) higher rank arrays

Arguments

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

Input matrix a(m,n)

character(len=*), intent(in) :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=sp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_3D_to_1D_char_d(a, order, dim, err) result(nrm)

Matrix norms: real(dp) higher rank arrays

Arguments

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

Input matrix a(m,n)

character(len=*), intent(in) :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=dp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_3D_to_1D_char_s(a, order, dim, err) result(nrm)

Matrix norms: real(sp) higher rank arrays

Arguments

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

Input matrix a(m,n)

character(len=*), intent(in) :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=sp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_3D_to_1D_char_z(a, order, dim, err) result(nrm)

Matrix norms: complex(dp) higher rank arrays

Arguments

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

Input matrix a(m,n)

character(len=*), intent(in) :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=dp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_3D_to_1D_int_c(a, order, dim, err) result(nrm)

Matrix norms: complex(sp) higher rank arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=sp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_3D_to_1D_int_d(a, order, dim, err) result(nrm)

Matrix norms: real(dp) higher rank arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=dp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_3D_to_1D_int_s(a, order, dim, err) result(nrm)

Matrix norms: real(sp) higher rank arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=sp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_3D_to_1D_int_z(a, order, dim, err) result(nrm)

Matrix norms: complex(dp) higher rank arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: order

Order of the matrix norm being computed.

integer(kind=ilp), intent(in), optional :: dim(2)

[optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])

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

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

Return Value real(kind=dp), allocatable, (:)

Norm of the matrix.

private module function matrix_norm_char_c(a, order, err) result(nrm)

Matrix norms: complex(sp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

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

Return Value real(kind=sp)

Norm of the matrix.

private module function matrix_norm_char_d(a, order, err) result(nrm)

Matrix norms: real(dp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

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

Return Value real(kind=dp)

Norm of the matrix.

private module function matrix_norm_char_s(a, order, err) result(nrm)

Matrix norms: real(sp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

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

Return Value real(kind=sp)

Norm of the matrix.

private module function matrix_norm_char_z(a, order, err) result(nrm)

Matrix norms: complex(dp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

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

Return Value real(kind=dp)

Norm of the matrix.

private module function matrix_norm_int_c(a, order, err) result(nrm)

Matrix norms: complex(sp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: 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

Return Value real(kind=sp)

Norm of the matrix.

private module function matrix_norm_int_d(a, order, err) result(nrm)

Matrix norms: real(dp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: 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

Return Value real(kind=dp)

Norm of the matrix.

private module function matrix_norm_int_s(a, order, err) result(nrm)

Matrix norms: real(sp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: 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

Return Value real(kind=sp)

Norm of the matrix.

private module function matrix_norm_int_z(a, order, err) result(nrm)

Matrix norms: complex(dp) rank-2 arrays

Arguments

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

Input matrix a(m,n)

integer(kind=ilp), intent(in), optional :: 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

Return Value real(kind=dp)

Norm of the matrix.