get_norm Interface

public interface get_norm

Vector norm: subroutine interface version: experimental

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

Summary

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.

Description

This pure subroutineinterface 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'

Example

    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)     

Subroutines

private pure module subroutine norm_1D_char_c(a, nrm, order, err)

Scalar norms: complex(sp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_1D_char_d(a, nrm, order, err)

Scalar norms: real(dp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_1D_char_s(a, nrm, order, err)

Scalar norms: real(sp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_1D_char_z(a, nrm, order, err)

Scalar norms: complex(dp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_1D_int_c(a, nrm, order, err)

Scalar norms: complex(sp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_1D_int_d(a, nrm, order, err)

Scalar norms: real(dp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_1D_int_s(a, nrm, order, err)

Scalar norms: real(sp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_1D_int_z(a, nrm, order, err)

Scalar norms: complex(dp)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_char_c(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_char_d(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_char_s(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_char_z(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_int_c(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_int_d(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_int_s(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_int_z(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_2D_to_1D_char_c(a, nrm, order, dim, err)

Array norms: complex(sp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_2D_to_1D_char_d(a, nrm, order, dim, err)

Array norms: real(dp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_2D_to_1D_char_s(a, nrm, order, dim, err)

Array norms: real(sp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_2D_to_1D_char_z(a, nrm, order, dim, err)

Array norms: complex(dp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_2D_to_1D_int_c(a, nrm, order, dim, err)

Array norms: complex(sp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_2D_to_1D_int_d(a, nrm, order, dim, err)

Array norms: real(dp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_2D_to_1D_int_s(a, nrm, order, dim, err)

Array norms: real(sp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_2D_to_1D_int_z(a, nrm, order, dim, err)

Array norms: complex(dp)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_char_c(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_char_d(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_char_s(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_char_z(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_int_c(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_int_d(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_int_s(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_int_z(a, nrm, order, err)

Arguments

Type IntentOptional 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

private pure module subroutine norm_3D_to_2D_char_c(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_to_2D_char_d(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_to_2D_char_s(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_to_2D_char_z(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_to_2D_int_c(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_to_2D_int_d(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_to_2D_int_s(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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

private pure module subroutine norm_3D_to_2D_int_z(a, nrm, order, dim, err)

Arguments

Type IntentOptional 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 a, with dim dropped).

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