Module_Utilities¶
Copyright 2018 IRD
This file is part of statpack.
statpack is free software: you can redistribute it and/or modify it under the terms of the GNU Lesser General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version.
statpack is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more details.
You can find a copy of the GNU Lesser General Public License in the statpack/doc directory.
MODULE EXPORTING GENERAL AND COMPUTING UTILITIES.
MANY OF THESE ROUTINES ARE ADAPTED AND EXTENDED FROM PUBLIC DOMAIN ROUTINES FROM Numerical Recipes.
LATEST REVISION : 21/09/2018
function dot_product2 ( vecx, vecy )
¶
Purpose¶
Forms the dot product of two complex vectors, conjugating the first vector
function mmproduct ( vec, mat )
¶
Purpose¶
Multiplies the complex vector VEC by the complex matrix MAT
function mmproduct ( mat, vec2 )
¶
Purpose¶
Multiplies the complex matrix MAT by the complex vector VEC2
function mmproduct ( mat1, mat2 )
¶
Purpose¶
Multiplies the complex matrix MAT1 by the complex matrix MAT2
function matmul2 ( vec, mat )
¶
Purpose¶
Multiplies the real vector VEC by the real matrix MAT
Further Details¶
This function will use the BLAS through the BLAS_interfaces module if the C processor macro _BLAS is activated during compilation. Furthermore, if the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat, vec2 )
¶
Purpose¶
Multiplies the real matrix MAT by the real vector VEC2
Further Details¶
This function will use the BLAS through the BLAS_interfaces module if the C processor macro _BLAS is activated during compilation. Furthermore, if the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat1, mat2 )
¶
Purpose¶
Multiplies the real matrix MAT1 by the real matrix MAT2
Further Details¶
This function will use the BLAS through the BLAS_interfaces module if the C processor macro _BLAS is activated during compilation. On the other hand, if the _BLAS macro is not activated and the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP if the matrices are big enough.
function matmul2 ( vec, mat )
¶
Purpose¶
Multiplies the complex vector VEC by the complex matrix MAT
Further Details¶
This function will use the BLAS through the BLAS_interfaces module if the C processor macro _BLAS is activated during compilation. Furthermore, if the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat, vec2 )
¶
Purpose¶
Multiplies the complex matrix MAT by the complex vector VEC2
Further Details¶
This function will use the BLAS through the BLAS_interfaces module if the C processor macro _BLAS is activated during compilation. Furthermore, if the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat1, mat2 )
¶
Purpose¶
Multiplies the complex matrix MAT1 by the complex matrix MAT2
Further Details¶
This function will use the BLAS through the BLAS_interfaces module if the C processor macro _BLAS is activated during compilation. On the other hand, if the _BLAS macro is not activated and the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP if the matrices are big enough.
function matmul2 ( vec, mat )
¶
Purpose¶
Multiplies the integer vector VEC by the integer matrix MAT
Further Details¶
If the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat, vec2 )
¶
Purpose¶
Multiplies the integer matrix MAT by the integer vector VEC2
Further Details¶
If the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat1, mat2 )
¶
Purpose¶
Multiplies the integer matrix MAT1 by the integer matrix MAT2
Further Details¶
If the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP if the matrices are big enough.
function matmul2 ( vec, mat )
¶
Purpose¶
Multiplies the logical vector VEC by the logical matrix MAT
Further Details¶
If the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat, vec2 )
¶
Purpose¶
Multiplies the logical matrix MAT by the logical vector VEC2
Further Details¶
If the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP.
function matmul2 ( mat1, mat2 )
¶
Purpose¶
Multiplies the logical matrix MAT1 by the logical matrix MAT2
Further Details¶
If the _OPENMP3 macro is activated during compilation, this function will be parallelized with OPENMP if the matrices are big enough.
subroutine array_copy ( src, dest, n_copied, n_not_copied )
¶
Purpose¶
Copies to a destination integer array DEST the one-dimensional integer array SRC, or as much of SRC as will fit in DEST.
Returns the number of components copied as N_COPIED, and the number of components not copied as N_NOT_COPIED.
subroutine array_copy ( src, dest, n_copied, n_not_copied )
¶
Purpose¶
Copies to a destination real array DEST the one-dimensional real array SRC, or as much of SRC as will fit in DEST.
Returns the number of components copied as N_COPIED, and the number of components not copied as N_NOT_COPIED.
subroutine array_copy ( src, dest, n_copied, n_not_copied )
¶
Purpose¶
Copies to a destination complex array DEST the one-dimensional complex array SRC, or as much of SRC as will fit in DEST.
Returns the number of components copied as N_COPIED, and the number of components not copied as N_NOT_COPIED.
subroutine swap ( a, b )
¶
Purpose¶
Swap the corresponding elements of the one-dimensional integer arrays A and B
subroutine swap ( a, b )
¶
Purpose¶
Swap the corresponding elements of the one-dimensional real arrays A and B
subroutine swap ( a, b )
¶
Purpose¶
Swap the corresponding elements of the one-dimensional complex arrays A and B
subroutine swap ( a, b )
¶
Purpose¶
Swap the corresponding elements of the two-dimensional integer arrays A and B
subroutine swap ( a, b )
¶
Purpose¶
Swap the corresponding elements of the two-dimensional real arrays A and B
subroutine swap ( a, b )
¶
Purpose¶
Swap the corresponding elements of the two-dimensional complex arrays A and B
subroutine swap ( a, b, mask )
¶
Purpose¶
Swap the corresponding elements of the one-dimensional integer arrays A and B, if the corresponding element of the one-dimensional logical array MASK is true.
subroutine swap ( a, b, mask )
¶
Purpose¶
Swap the corresponding elements of the one-dimensional real arrays A and B, if the corresponding element of the one-dimensional logical array MASK is true.
subroutine swap ( a, b, mask )
¶
Purpose¶
Swap the corresponding elements of the one-dimensional complex arrays A and B, if the corresponding element of the one-dimensional logical array MASK is true.
subroutine swap ( a, b, mask )
¶
Purpose¶
Swap the corresponding elements of the two-dimensional integer arrays A and B, if the corresponding element of the two-dimensional logical array MASK is true.
subroutine swap ( a, b, mask )
¶
Purpose¶
Swap the corresponding elements of the two-dimensional real arrays A and B, if the corresponding element of the two-dimensional logical array MASK is true.
subroutine swap ( a, b, mask )
¶
Purpose¶
Swap the corresponding elements of the two-dimensional complex arrays A and B, if the corresponding element of the two-dimensional logical array MASK is true.
subroutine mvalloc ( p, n, ialloc )
¶
Purpose¶
Reallocates an allocatable array P to an integer one dimensional array with a new size N, while preserving its contents.
subroutine mvalloc ( p, n, ialloc )
¶
Purpose¶
Reallocates an allocatable array P to a real one dimensional array with a new size N, while preserving its contents.
subroutine mvalloc ( p, n, ialloc )
¶
Purpose¶
Reallocates an allocatable array P to a complex one dimensional array with a new size N, while preserving its contents.
subroutine mvalloc ( p, n, ialloc )
¶
Purpose¶
Reallocates an allocatable array P to a character one dimensional array with a new size N, while preserving its contents.
subroutine mvalloc ( p, n, m, ialloc )
¶
Purpose¶
Reallocates an allocatable array P to an integer two dimensional array with a new shape (N,M) while preserving its contents.
subroutine mvalloc ( p, n, m, ialloc )
¶
Purpose¶
Reallocates an allocatable array P to a real two dimensional array with a new shape (N,M) while preserving its contents.
subroutine mvalloc ( p, n, m, ialloc )
¶
Purpose¶
Reallocates an allocatable array P to a complex two dimensional array with a new shape (N,M) while preserving its contents.
function ifirstloc ( mask )
¶
Purpose¶
Returns the index of the first location, in a one-dimensional logical MASK, that has the value true, or returns size(MASK)+1 if all components of MASK are false .
function imaxloc ( arr )
¶
Purpose¶
Returns location of the one-dimensional integer array ARR maximum as an integer.
function imaxloc ( arr, mask )
¶
Purpose¶
Returns location as an integer of the maximum in the elements of the one-dimensional integer array ARR under the control of the one-dimensional logical array MASK. Returns size(MASK)+1 if all components of MASK are false .
function imaxloc ( arr )
¶
Purpose¶
Returns location of the one-dimensional real array ARR maximum as an integer.
function imaxloc ( arr, mask )
¶
Purpose¶
Returns location as an integer of the maximum in the elements of the one-dimensional real array ARR under the control of the one-dimensional logical array MASK. Returns size(MASK)+1 if all components of MASK are false .
function iminloc ( arr )
¶
Purpose¶
Returns location of the one-dimensional integer array ARR minimum as an integer.
function iminloc ( arr, mask )
¶
Purpose¶
Returns location as an integer of the minimum in the elements of the one-dimensional integer array ARR under the control of the one-dimensional logical array MASK. Returns size(MASK)+1 if all components of MASK are false .
function iminloc ( arr )
¶
Purpose¶
Returns location of the one-dimensional real array ARR minimum as an integer.
function iminloc ( arr, mask )
¶
Purpose¶
Returns location as an integer of the minimum in the elements of the one-dimensional real array ARR under the control of the one-dimensional logical array MASK. Returns size(MASK)+1 if all components of MASK are false .
subroutine assert ( n1, string )
¶
Purpose¶
Exit with error message STRING, if logical argument n1 is false .
subroutine assert ( n1, n2, string )
¶
Purpose¶
Exit with error message STRING, if any of the logical arguments n1, n2 are false .
subroutine assert ( n1, n2, n3, string )
¶
Purpose¶
Exit with error message STRING, if any of the logical arguments n1, n2, n3 are false .
subroutine assert ( n1, n2, n3, n4, string )
¶
Purpose¶
Exit with error message STRING, if any of the logical arguments n1, n2, n3, n4 are false .
subroutine assert ( n, string )
¶
Purpose¶
Exit with error message STRING, if any of the elements of the one-dimensional logical array N are false .
function assert_eq ( n1, n2, string )
¶
Purpose¶
Exit with error message STRING, if the integer arguments n1, n2 are not equal.
function assert_eq ( n1, n2, n3, string )
¶
Purpose¶
Exit with error message STRING, if the integer arguments n1, n2, n3 are not all equal.
function assert_eq ( n1, n2, n3, n4, string )
¶
Purpose¶
Exit with error message STRING, if the integer arguments n1, n2, n3, n4 are not all equal.
function assert_eq ( nn, string )
¶
Purpose¶
Exit with error message STRING, if the elements of the one-dimensional integer array NN are not all equal.
subroutine merror ( string, ierror )
¶
Purpose¶
Report error message STRING and optional error number IERROR and stop.
function arth ( first, increment, n )
¶
Purpose¶
Returns an one-dimensional integer array of length N containing an arithmetic progression whose first value is FIRST and whose increment is INCREMENT.
function arth ( first, increment, n )
¶
Purpose¶
Returns an one-dimensional real array of length N containing an arithmetic progression whose first value is FIRST and whose increment is INCREMENT.
function arth ( first, increment, n )
¶
Purpose¶
Returns an one-dimensional complex array of length N containing an arithmetic progression whose first value is FIRST and whose increment is INCREMENT.
function arth ( first, increment, n )
¶
Purpose¶
Returns a two-dimensional integer array containing size(FIRST) = size(INCREMENT) arithmetic progressions of length N whose first values are FIRST(:) and whose increments are INCREMENT(:).
It is assumed that the vector arguments FIRST and INCREMENT have the same length.
function arth ( first, increment, n )
¶
Purpose¶
Returns a two-dimensional real array containing size(FIRST) = size(INCREMENT) arithmetic progressions of length N whose first values are FIRST(:) and whose increments are INCREMENT(:).
It is assumed that the vector arguments FIRST and INCREMENT have the same length.
function arth ( first, increment, n )
¶
Purpose¶
Returns a two-dimensional complex array containing size(FIRST) = size(INCREMENT) arithmetic progressions of length N whose first values are FIRST(:) and whose increments are INCREMENT(:).
It is assumed that the vector arguments FIRST and INCREMENT have the same length.
function geop ( first, factor, n )
¶
Purpose¶
Returns an one-dimensional integer array of length N containing a geometric progression whose first value is FIRST and whose multiplier is FACTOR.
function geop ( first, factor, n )
¶
Purpose¶
Returns an one-dimensional real array of length N containing a geometric progression whose first value is FIRST and whose multiplier is FACTOR.
function geop ( first, factor, n )
¶
Purpose¶
Returns an one-dimensional complex array of length N containing a geometric progression whose first value is FIRST and whose multiplier is FACTOR.
function geop ( first, factor, n )
¶
Purpose¶
Returns a two-dimensional integer array containing size(FIRST) = size(FACTOR) geometric progressions of length N whose first values are FIRST(:) and whose multipliers are FACTOR(:).
It is assumed that the vector arguments FIRST and FACTOR have the same length.
function geop ( first, factor, n )
¶
Purpose¶
Returns a two-dimensional real array containing size(FIRST) = size(FACTOR) geometric progressions of length N whose first values are FIRST(:) and whose multipliers are FACTOR(:).
It is assumed that the vector arguments FIRST and FACTOR have the same length.
function geop ( first, factor, n )
¶
Purpose¶
Returns a two-dimensional complex array containing size(FIRST) = size(FACTOR) geometric progressions of length N whose first values are FIRST(:) and whose multipliers are FACTOR(:).
It is assumed that the vector arguments FIRST and FACTOR have the same length.
function cumsum ( arr, seed )
¶
Purpose¶
Returns a rank one integer array containing the cumulative sum of the rank one integer array ARR. If the optional argument SEED is present, it is added to all components of the result.
function cumsum ( arr, seed )
¶
Purpose¶
Returns a rank one real array containing the cumulative sum of the rank one real array ARR. If the optional argument SEED is present, it is added to all components of the result.
function cumsum ( arr, seed )
¶
Purpose¶
Returns a rank one complex array containing the cumulative sum of the rank one complex array ARR. If the optional argument SEED is present, it is added to all components of the result.
function cumprod ( arr, seed )
¶
Purpose¶
Returns a rank one integer array containing the cumulative product of the rank one integer array ARR. If the optional argument SEED is present, it is multiplied into all components of the result.
function cumprod ( arr, seed )
¶
Purpose¶
Returns a rank one real array containing the cumulative product of the rank one real array ARR. If the optional argument SEED is present, it is multiplied into all components of the result.
function cumprod ( arr, seed )
¶
Purpose¶
Returns a rank one complex array containing the cumulative product of the rank one complex array ARR. If the optional argument SEED is present, it is multiplied into all components of the result.
function poly ( x, coeffs )
¶
Purpose¶
Returns a real scalar containing the result of evaluating the polynomial P(X) for X real with one-dimensional real coefficient vector COEFFS
P(X) = COEFFS(1) + COEFFS(2) * X + COEFFS(3) * X**(2) + …
function poly ( x, coeffs )
¶
Purpose¶
Returns a complex scalar containing the result of evaluating the polynomial P(X) for X complex with one-dimensional real coefficient vector COEFFS
P(X) = COEFFS(1) + COEFFS(2) * X + COEFFS(3) * X**(2) + …
function poly ( x, coeffs )
¶
Purpose¶
Returns a complex scalar containing the result of evaluating the polynomial P(X) for X complex with one-dimensional complex coefficient vector COEFFS
P(X) = COEFFS(1) + COEFFS(2) * X + COEFFS(3) * X**(2) + …
function poly ( x, coeffs )
¶
Purpose¶
Returns a real vector containing the results of evaluating the polynomials P(X(:)) for X(:) real with one-dimensional real coefficient vector COEFFS
P(X(:)) = COEFFS(1) + COEFFS(2) * X(:) + COEFFS(3) * X(:)**(2) + …
function poly ( x, coeffs, mask )
¶
Purpose¶
Returns a real vector containing the results of evaluating the polynomials P(X(:)) for X(:) real with one-dimensional real coefficient vector COEFFS
P(X(:)) = COEFFS(1) + COEFFS(2) * X(:) + COEFFS(3) * X(:)**(2) + …under the control of the logical argument MASK. If MASK(i) = false, the polynomial is not evaluated at X(i).
function poly_term ( coeffs, x )
¶
Purpose¶
Returns a real array of size(COEFFS) containing the partial cumulants of the polynomial with real coefficients COEFFS evaluated at the real scalar X. On entry, the coefficients in COEFFS are arranged from highest order to lowest-order coefficients.
function poly_term ( coeffs, x )
¶
Purpose¶
Returns a complex array of size(COEFFS) containing the partial cumulants of the polynomial with complex coefficients COEFFS evaluated at the complex scalar X. On entry, the coefficients in COEFFS are arranged from highest order to lowest-order coefficients.
function zroots_unity ( n, nn )
¶
Purpose¶
Complex function returning a complex array containing nn consecutive powers of the nth complex root of unity.
subroutine update_rk1 ( mat, u, v )
¶
Purpose¶
Updates the integer matrix MAT with the outer sum of the two integer vectors U and V :
MAT = MAT + U * V’
subroutine update_rk1 ( mat, u, v )
¶
Purpose¶
Updates the real matrix MAT with the outer sum of the two reals vectors U and V :
MAT = MAT + U * V’
subroutine update_rk1 ( mat, u, v )
¶
Purpose¶
Updates the complex matrix MAT with the outer sum of the two complex vectors U and V :
MAT = MAT + U * V’
subroutine update_rk2 ( mat, u, v, u2, v2 )
¶
Purpose¶
Updates the integer matrix MAT with the outer sums of the integer vectors U, V, U2 and V2:
MAT = MAT + U * V’ + U2 * V2’
subroutine update_rk2 ( mat, u, v, u2, v2 )
¶
Purpose¶
Updates the real matrix MAT with the outer sums of the real vectors U, V, U2 and V2:
MAT = MAT + U * V’ + U2 * V2’
subroutine update_rk2 ( mat, u, v, u2, v2 )
¶
Purpose¶
Updates the complex matrix MAT with the outer sums of the complex vectors U, V, U2 and V2:
MAT = MAT + U * V’ + U2 * V2’
function outerprod ( a, b )
¶
Purpose¶
Returns a matrix that is the outer product of the two integer vectors A and B .
function outerprod ( a, b )
¶
Purpose¶
Returns a matrix that is the outer product of the two real vectors A and B .
function outerprod ( a, b )
¶
Purpose¶
Returns a matrix that is the outer product of the two complex vectors A and B .
function outerdiv ( a, b )
¶
Purpose¶
Returns a matrix that is the outer quotient of the two real vectors A and B .
Further Details¶
It is assumed that none of the elements of B is zero.
function outerdiv ( a, b )
¶
Purpose¶
Returns a matrix that is the outer quotient of the two complex vectors A and B .
Further Details¶
It is assumed that none of the elements of B is zero.
function outersum ( a, b )
¶
Purpose¶
Returns a matrix that is the outer sum of the two integer vectors A and B .
Further Details¶
It is assumed that none of the elements of B is zero.
function outersum ( a, b )
¶
Purpose¶
Returns a matrix that is the outer sum of the two real vectors A and B .
function outersum ( a, b )
¶
Purpose¶
Returns a matrix that is the outer sum of the two complex vectors A and B .
function outerdiff ( a, b )
¶
Purpose¶
Returns a matrix that is the outer difference of the two integer vectors A and B .
function outerdiff ( a, b )
¶
Purpose¶
Returns a matrix that is the outer difference of the two real vectors A and B .
function outerdiff ( a, b )
¶
Purpose¶
Returns a matrix that is the outer difference of the two complex vectors A and B .
function outerand ( a, b )
¶
Purpose¶
Returns a matrix that is the outer logical AND of two logical vectors A and B .
function outeror ( a, b )
¶
Purpose¶
Returns a matrix that is the outer logical OR of two logical vectors A and B .
function triangle ( upper, j, k, extra )
¶
Purpose¶
Return an upper (if UPPER=true) or lower (if UPPER=false) triangular logical mask.
function abse ( vec )
¶
Purpose¶
Return the ordinary L2 norm of the complex vector VEC as a real scalar.
function abse ( mat )
¶
Purpose¶
Return the Froebenius norm of the complex matrix MAT as a real scalar.
function abse ( mat, dim )
¶
Purpose¶
Return the ordinary L2 norm of the column vectors (DIM=2) or the row vectors (DIM=1) of the real matrix MAT as a real vector.
function abse ( mat, dim )
¶
Purpose¶
Return the ordinary L2 norm of the column vectors (DIM=2) or the row vectors (DIM=1) of the complex matrix MAT as a real vector.
subroutine lassq ( vec, scal, ssq )
¶
Purpose¶
LASSQ returns the values scl and smsq such that
( scl**(2) ) * smsq = sum( VEC**(2) ) + ( scale**(2) )*ssq,The value of ssq is assumed to be non-negative and scl returns the value
scl = max( scale, maxval( abs( VEC ) ) ).scale and ssq must be supplied in SCAL and SSQ and scl and smsq are overwritten on SCAL and SSQ respectively.
Arguments¶
- VEC (INPUT) real(stnd), dimension(:)
- The real vector for which a scaled sum of squares is computed.
- SCAL (INPUT/OUTPUT) real(stnd)
- On entry, the value scale in the equation above. On exit, SCAL is overwritten with scl , the scaling factor for the sum of squares.
- SSQ (INPUT/OUTPUT) real(stnd)
- On entry, the value ssq in the equation above. On exit, SSQ is overwritten with smsq , the basic sum of squares from which scl has been factored out.
subroutine lassq ( vec, scal, ssq )
¶
Purpose¶
LASSQ_CV returns the values scl and smsq such that
( scl**(2) ) * smsq = dot_product( VEC, VEC ) + ( scale**(2) ) * ssq,The value of ssq is assumed to be non-negative and scl returns the value
scl = max( scale, maxval(abs(real(VEC))), maxval(abs(aimag(VEC))) ).scale and ssq must be supplied in SCAL and SSQ and scl and smsq are overwritten on SCAL and SSQ respectively.
Arguments¶
- VEC (INPUT) complex(stnd), dimension(:)
- The complex vector for which a scaled sum of squares is computed.
- SCAL (INPUT/OUTPUT) real(stnd)
- On entry, the value scale in the equation above. On exit, SCAL is overwritten with scl , the scaling factor for the sum of squares.
- SSQ (INPUT/OUTPUT) real(stnd)
- On entry, the value ssq in the equation above. On exit, SSQ is overwritten with smsq , the basic sum of squares from which scl has been factored out.
subroutine lassq ( mat, scal, ssq )
¶
Purpose¶
LASSQ returns the values scl and smsq such that
( scl**(2) ) * smsq = sum( MAT**(2) ) + ( scale**(2) ) * ssq,The value of ssq is assumed to be non-negative and scl returns the value
scl = max( scale, maxval(abs(MAT)) ).scale and ssq must be supplied in SCAL and SSQ and scl and smsq are overwritten on SCAL and SSQ respectively.
Arguments¶
- MAT (INPUT) real(stnd), dimension(:,:)
- The matrix for which a scaled sum of squares is computed.
- SCAL (INPUT/OUTPUT) real(stnd)
- On entry, the value scale in the equation above. On exit, SCAL is overwritten with scl , the scaling factor for the sum of squares.
- SSQ (INPUT/OUTPUT) real(stnd)
- On entry, the value ssq in the equation above. On exit, SSQ is overwritten with smsq , the basic sum of squares from which scl has been factored out.
subroutine lassq ( mat, scal, ssq )
¶
Purpose¶
LASSQ returns the values scl and smsq such that
( scl**(2) ) * smsq = sum( MAT * conjg(MAT) ) + ( scale**(2) ) * ssq,The value of ssq is assumed to be non-negative and scl returns the value
scl = max( scale, maxval(abs(real(MAT))), maxval(abs(aimag(MAT))) ).scale and ssq must be supplied in SCAL and SSQ and scl and smsq are overwritten on SCAL and SSQ respectively.
Arguments¶
- MAT (INPUT) complex(stnd), dimension(:,:)
- The complex matrix for which a scaled sum of squares is computed.
- SCAL (INPUT/OUTPUT) real(stnd)
- On entry, the value scale in the equation above. On exit, SCAL is overwritten with scl , the scaling factor for the sum of squares.
- SSQ (INPUT/OUTPUT) real(stnd)
- On entry, the value ssq in the equation above. On exit, SSQ is overwritten with smsq , the basic sum of squares from which scl has been factored out.
function norm ( vec )
¶
Purpose¶
Return the Euclidean norm of the real vector VEC via the function name, so that
norm_rv := sqrt( VEC * VEC )This is done without destructive underflow or overflow.
function norm ( vec )
¶
Purpose¶
Return the Euclidean norm of the complex vector VEC via the function name, so that
norm_cv := sqrt( dot_product(VEC,VEC) )This is done without destructive underflow or overflow.
function norm ( mat )
¶
Purpose¶
Return the Froebenius norm of the real matrix MAT via the function name, so that
norm_rm := sqrt( MAT * MAT )This is done without destructive underflow or overflow.
function norm ( mat )
¶
Purpose¶
Return the Froebenius norm of the complex matrix MAT via the function name, so that
norm_cm := sqrt( MAT * conjg(MAT) )This is done without destructive underflow or overflow.
function norm ( mat, dim )
¶
Purpose¶
Return the Euclidean norms of the columns (DIM=2) or of the rows (DIM=1) of a real matrix MAT via the function name, so that
norm_dim_rm := sqrt( sum(MAT * MAT,dim=3-dim) )This is done without destructive underflow or overflow.
function norm ( mat, dim )
¶
Purpose¶
Return the Euclidean norms of the columns (DIM=2) or of the rows (DIM=1) of a complex matrix MAT via the function name, so that
norm_dim_cm := sqrt( sum(MAT * conjg(MAT),dim=3-dim) )This is done without destructive underflow or overflow.
subroutine scatter_add ( dest, source, dest_index )
¶
Purpose¶
Adds each component of the integer vector SOURCE into a component of the integer vector DEST specified by the index vector DEST_INDEX.
subroutine scatter_add ( dest, source, dest_index )
¶
Purpose¶
Adds each component of the real vector SOURCE into a component of the real vector DEST specified by the index vector DEST_INDEX.
subroutine scatter_add ( dest, source, dest_index )
¶
Purpose¶
Adds each component of the complex vector SOURCE into a component of the complex vector DEST specified by the index vector DEST_INDEX.
subroutine scatter_max ( dest, source, dest_index )
¶
Purpose¶
Takes the max operation between each component of the real vector SOURCE and a component of the real vector DEST specified by the index vector DEST_INDEX, replacing the component of DEST with the value obtained.
subroutine scatter_max ( dest, source, dest_index )
¶
Purpose¶
Takes the max operation between each component of the integer vector SOURCE and a component of the integer vector DEST specified by the index vector DEST_INDEX, replacing the component of DEST with the value obtained.
subroutine diagadd ( mat, diag )
¶
Purpose¶
Adds real vector DIAG to the diagonal of real matrix MAT.
subroutine diagadd ( mat, diag )
¶
Purpose¶
Adds complex vector DIAG to the diagonal of complex matrix MAT.
subroutine diagadd ( mat, diag )
¶
Purpose¶
Adds real scalar DIAG to the diagonal of real matrix MAT.
subroutine diagadd ( mat, diag )
¶
Purpose¶
Adds complex scalar DIAG to the diagonal of complex matrix MAT.
subroutine diagmult ( mat, diag )
¶
Purpose¶
Multiplies real vector DIAG into the diagonal of real matrix MAT.
subroutine diagmult ( mat, diag )
¶
Purpose¶
Multiplies complex vector DIAG into the diagonal of complex matrix MAT.
subroutine diagmult ( mat, diag )
¶
Purpose¶
Multiplies real scalar DIAG into the diagonal of real matrix MAT.
subroutine diagmult ( mat, diag )
¶
Purpose¶
Multiplies complex scalar DIAG into the diagonal of complex matrix MAT.
subroutine put_diag ( diag, mat )
¶
Purpose¶
Set the diagonal of real matrix MAT to the values of the real vector DIAG.
subroutine put_diag ( diag, mat )
¶
Purpose¶
Set the diagonal of complex matrix MAT to the values of the complex vector DIAG.
subroutine put_diag ( diag, mat )
¶
Purpose¶
Set the diagonal of real matrix MAT to the value of the real scalar DIAG.
subroutine put_diag ( diag, mat )
¶
Purpose¶
Set the diagonal of complex matrix MAT to the value of the complex scalar DIAG.
subroutine unit_matrix ( mat )
¶
Purpose¶
Set the real matrix MAT to be a unit real matrix (if it is square).
subroutine unit_matrix ( mat )
¶
Purpose¶
Set the complex matrix MAT to be a unit complex matrix (if it is square).
subroutine lascl ( x, cfrom, cto )
¶
Purpose¶
LASCL multiplies the real scalar X by the real scalar CTO/CFROM . This is done without over/underflow as long as the final result CTO * X/CFROM does not over/underflow. CFROM must be nonzero.
Arguments¶
- X (INPUT/OUTPUT) real(stnd)
- The real to be multiplied by CTO/CFROM.
- CFROM, CTO (INPUT) real(stnd)
- The real X is multiplied by CTO/CFROM.
Further Details¶
This subroutine is adapted from the routine DLASCL in LAPACK77 (version 3) with improvements suggested by E. Anderson. See
- Anderson, LAPACK3E – A Fortran90-enhanced version of LAPACK. Lapack Working Note 158,
- University of Tennessee, December 2002.
subroutine lascl ( x, cfrom, cto )
¶
Purpose¶
LASCL multiplies the real vector X by the real scalar CTO/CFROM . This is done without over/underflow as long as the final result CTO * X(i)/CFROM does not over/underflow for i = 1 to size( X).
CFROM must be nonzero.
Arguments¶
- X (INPUT/OUTPUT) real(stnd), dimension(:)
- The real vector to be multiplied by CTO/CFROM.
- CFROM, CTO (INPUT) real(stnd)
- The real vector X is multiplied by CTO/CFROM.
Further Details¶
This subroutine is adapted from the routine DLASCL in LAPACK77 (version 3) with improvements suggested by E. Anderson. See
- Anderson, LAPACK3E – A Fortran90-enhanced version of LAPACK. Lapack Working Note 158,
- University of Tennessee, December 2002.
subroutine lascl ( x, cfrom, cto )
¶
Purpose¶
LASCL multiplies the real matrix X by the real scalar CTO/CFROM . This is done without over/underflow as long as the final result CTO * X(i,j)/CFROM does not over/underflow for i = 1 to size( X, 1) and j = 1 to size( X, 2).
CFROM must be nonzero.
Arguments¶
- X (INPUT/OUTPUT) real(stnd), dimension(:,:)
- The real matrix to be multiplied by CTO/CFROM.
- CFROM, CTO (INPUT) real(stnd)
- The real matrix X is multiplied by CTO/CFROM.
Further Details¶
This subroutine is adapted from the routine DLASCL in LAPACK77 (version 3) with improvements suggested by E. Anderson. See
- Anderson, LAPACK3E – A Fortran90-enhanced version of LAPACK. Lapack Working Note 158,
- University of Tennessee, December 2002.
subroutine lascl ( x, cfrom, cto, type )
¶
Purpose¶
LASCL multiplies the real matrix X by the real scalar CTO/CFROM . This is done without over/underflow as long as the final result CTO * X(i,j)/CFROM does not over/underflow for i = 1 to size( X, 1) and j = 1 to size( X, 2).
CFROM must be nonzero.
TYPE specifies that X may be full, upper triangular, lower triangular or upper Hessenberg.
Arguments¶
- X (INPUT/OUTPUT) real(stnd), dimension(:,:)
- The real matrix to be multiplied by CTO/CFROM.
- CFROM, CTO (INPUT) real(stnd)
- The real matrix X is multiplied by CTO/CFROM.
- TYPE (INPUT) character*1
- TYPE indices the storage type of the input matrix. = ‘L’ or ‘l’: X is a lower triangular matrix. = ‘U’ or ‘u’: X is a upper triangular matrix. = ‘H’ or ‘h’: X is a upper Hessenberg matrix. = ‘G’ or ‘g’: X is a full matrix. = any other character: X is assumed to be a full matrix.
Further Details¶
This subroutine is adapted from the routine DLASCL in LAPACK77 (version 3) with improvements suggested by E. Anderson. See
- Anderson, LAPACK3E – A Fortran90-enhanced version of LAPACK. Lapack Working Note 158,
- University of Tennessee, December 2002.
subroutine lascl ( x, cfrom, cto, mask )
¶
Purpose¶
LASCL multiplies the real scalar X by the real scalar CTO/CFROM under the control of the logical argument MASK . This is done without over/underflow as long as the final result CTO * X/CFROM does not over/underflow.
CFROM must be nonzero.
Arguments¶
- X (INPUT/OUTPUT) real(stnd)
- The real to be multiplied by CTO/CFROM.
- CFROM, CTO (INPUT) real(stnd)
- The real X is multiplied by CTO/CFROM if MASK=true.
- MASK (INPUT) logical(lgl)
- The logical mask : if MASK=true the multiplication is done, otherwise X is left unchanged.
Further Details¶
This subroutine is adapted from the routine DLASCL in LAPACK77 (version 3) with improvements suggested by E. Anderson. See
- Anderson, LAPACK3E – A Fortran90-enhanced version of LAPACK. Lapack Working Note 158,
- University of Tennessee, December 2002.
subroutine lascl ( x, cfrom, cto, mask )
¶
Purpose¶
LASCL multiplies the real vector X by the real scalar CTO/CFROM under the control of the logical argument MASK . This is done without over/underflow as long as the final result CTO * X(i)/CFROM does not over/underflow for i = 1 to size( X).
CFROM must be nonzero.
Arguments¶
- X (INPUT/OUTPUT) real(stnd), dimension(:)
- The real vector to be multiplied by CTO/CFROM.
- CFROM, CTO (INPUT) real(stnd)
- The real X(i) is multiplied by CTO/CFROM if MASK(i)=true.
- MASK (INPUT) logical(lgl), dimension(:)
- The logical mask : if MASK(i)=true the multiplication is done, otherwise X(i) is left unchanged.
Further Details¶
This subroutine is adapted from the routine DLASCL in LAPACK77 (version 3) with improvements suggested by E. Anderson. See
- Anderson, LAPACK3E – A Fortran90-enhanced version of LAPACK. Lapack Working Note 158,
- University of Tennessee, December 2002.
The sizes of X and MASK must match.
subroutine lascl ( x, cfrom, cto, mask )
¶
Purpose¶
LASCL multiplies the real matrix X by the real scalar CTO/CFROM under the control of the logical argument MASK . This is done without over/underflow as long as the final result CTO * X(i,j)/CFROM does not over/underflow for i = 1 to size( X, 1) and j = 1 to size( X, 2).
CFROM must be nonzero.
Arguments¶
- X (INPUT/OUTPUT) real(stnd), dimension(:,:)
- The real matrix to be multiplied by CTO/CFROM.
- CFROM, CTO (INPUT) real(stnd)
- The real X(i,j) is multiplied by CTO/CFROM if MASK(i,j)=true.
- MASK (INPUT) logical(lgl), dimension(:,:)
- The logical mask : if MASK(i,j)=true the multiplication is done, otherwise X(i,j) is left unchanged.
Further Details¶
This subroutine is adapted from the routine DLASCL in LAPACK77 (version 3) with improvements suggested by E. Anderson. See
- Anderson, LAPACK3E – A Fortran90-enhanced version of LAPACK. Lapack Working Note 158,
- University of Tennessee, December 2002.
The shapes of X and MASK must match.
function norme ( vec )
¶
Purpose¶
This function computes the 2-norm (i.e. the Euclidean norm) of the vector VEC of length n, with due regard to avoiding overflow and underflow.
Arguments¶
- VEC (INPUT) real(stnd), dimension(:)
- On entry, the real vector VEC.
Further Details¶
The routine is based on snrm2 from the blas (in linpack), but this version is written in Fortran 90. It is machine independent. The algorithm is described in
- J.L. Blue, A portable Fortran program to find the Euclidean norm of
- a vector. ACM Trans. Math. Soft., Vol. 4, No 1, 1978, pp.15-23
The machine constants MACHTINY (the smallest magnitude), MACHBASE(base of the machine), and MACHEPS (epsilon) are used to calculate the constants cutlo and cuthi:
cutlo = sqrt( machsmlnum ) = sqrt( MACHTINY/(MACHEPS * MACHBASE) ) cuthi = one/cutloThree different cases must be considered when calculating the norm:
All components of VEC are below cutlo.
To avoid underflow, each component is divided by sqrt(min)/n and then the regular Euclidean norm of this modified vector is calculated. This result is then multiplied by sqrt(min)/n in order to get the correct value for the norm.
One or more components are greater than cuthi.
To avoid overflow, the same method as in case (1) is used with a scaling factor of sqrt(max) * n .
All components are less than cuthi, with at least one component greater than cutlo.
The regular formula for the Euclidean norm is used.
function norme ( mat )
¶
Purpose¶
This function computes the 2-norm (i.e. the Frobenius norm) of the matrix MAT of size n, with due regard to avoiding overflow and underflow.
Arguments¶
- MAT (INPUT) real(stnd), dimension(:,:)
- On entry, the real matrix MAT.
Further Details¶
The routine is based on snrm2 from the blas (in linpack), but this version is written in Fortran 90. It is machine independent. The algorithm is described in
- J.L. Blue, A portable Fortran program to find the Euclidean norm of
- a vector. ACM Trans. Math. Soft., Vol. 4, No 1, 1978, pp.15-23
The machine constants MACHTINY (the smallest magnitude), MACHBASE(base of the machine), and MACHEPS (epsilon) are used to calculate the constants cutlo and cuthi:
cutlo = sqrt( machsmlnum ) = sqrt( MACHTINY/(MACHEPS * MACHBASE) ) cuthi = one/cutloThree different cases must be considered when calculating the norm:
All components of MAT are below cutlo.
To avoid underflow, each component is divided by sqrt(min)/n and then the regular Euclidean norm of this modified vector is calculated. This result is then multiplied by sqrt(min)/n in order to get the correct value for the norm.
One or more components are greater than cuthi.
To avoid overflow, the same method as in case (1) is used with a scaling factor of sqrt(max) * n .
All components are less than cuthi, with at least one component greater than cutlo.
The regular formula for the Frobenius norm is used.