norm Interface

public interface norm

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

Summary

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.

Description

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'

Example

    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)

Functions

private pure module function stdlib_linalg_norm_1D_order_char_c(a, order) result(nrm)

Scalar norms: complex(sp)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_1D_order_char_d(a, order) result(nrm)

Scalar norms: real(dp)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_1D_order_char_s(a, order) result(nrm)

Scalar norms: real(sp)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_1D_order_char_z(a, order) result(nrm)

Scalar norms: complex(dp)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_1D_order_int_c(a, order) result(nrm)

Scalar norms: complex(sp)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_1D_order_int_d(a, order) result(nrm)

Scalar norms: real(dp)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_1D_order_int_s(a, order) result(nrm)

Scalar norms: real(sp)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_1D_order_int_z(a, order) result(nrm)

Scalar norms: complex(dp)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_char_c(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_char_d(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_char_s(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_char_z(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_int_c(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_int_d(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_int_s(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_order_int_z(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_2D_to_1D_char_c(a, order, dim) result(nrm)

Array norms: complex(sp)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_2D_to_1D_char_d(a, order, dim) result(nrm)

Array norms: real(dp)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_2D_to_1D_char_s(a, order, dim) result(nrm)

Array norms: real(sp)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_2D_to_1D_char_z(a, order, dim) result(nrm)

Array norms: complex(dp)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_2D_to_1D_int_c(a, order, dim) result(nrm)

Array norms: complex(sp)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_2D_to_1D_int_d(a, order, dim) result(nrm)

Array norms: real(dp)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_2D_to_1D_int_s(a, order, dim) result(nrm)

Array norms: real(sp)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_2D_to_1D_int_z(a, order, dim) result(nrm)

Array norms: complex(dp)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_order_char_c(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_order_char_d(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_order_char_s(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_order_char_z(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

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

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_order_int_c(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_order_int_d(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_order_int_s(a, order) result(nrm)

Arguments

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

Return Value real(kind=sp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_order_int_z(a, order) result(nrm)

Arguments

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

Return Value real(kind=dp)

Norm of the matrix.

private pure module function stdlib_linalg_norm_3D_to_2D_char_c(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_to_2D_char_d(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_to_2D_char_s(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_to_2D_char_z(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

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

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_to_2D_int_c(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_to_2D_int_d(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_to_2D_int_s(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=sp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).

private pure module function stdlib_linalg_norm_3D_to_2D_int_z(a, order, dim) result(nrm)

Arguments

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

Return Value real(kind=dp), (merge(size(a,1),size(a,2),mask=1

Norm of the matrix. (Same shape as a, with dim dropped).


Fortran-lang/stdlib was developed by fortran-lang/stdlib contributors
© 2024 Creative Commons License
38e8e0e7

Documentation generated by FORD on 2024-10-22 06:51