CDOTC forms the dot product of two complex vectors CDOTC = X^H * Y
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | cy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CDOTU forms the dot product of two complex vectors CDOTU = X^T * Y
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | cy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CAXPY constant times a vector plus a vector.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | ca | |||
complex(kind=sp), | intent(in) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(inout) | :: | cy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CCOPY copies a vector x to a vector y.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(out) | :: | cy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | kl | |||
integer(kind=ilp), | intent(in) | :: | ku | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | transa | |||
character(len=1), | intent(in) | :: | transb | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
CGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CGERC performs the rank 1 operation A := alphaxy**H + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
complex(kind=sp), | intent(inout) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda |
CGERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
complex(kind=sp), | intent(inout) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda |
CHBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CHEMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is an hermitian matrix and B and C are m by n matrices.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | side | |||
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
CHEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CHER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
real(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(inout) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda |
CHER2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
complex(kind=sp), | intent(inout) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda |
CHER2K performs one of the hermitian rank 2k operations C := alphaABH + conjg( alpha )BAH + betaC, or C := alphaAHB + conjg( alpha )BHA + betaC, where alpha and beta are scalars with beta real, C is an n by n hermitian matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb | |||
real(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
CHERK performs one of the hermitian rank k operations C := alphaAAH + betaC, or C := alphaAHA + betaC, where alpha and beta are real scalars, C is an n by n hermitian matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
real(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
real(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
CHPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | ap(*) | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CHPR performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix, supplied in packed form.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
real(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(inout) | :: | ap(*) |
CHPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(in) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
complex(kind=sp), | intent(inout) | :: | ap(*) |
The computation uses the formulas |x| = sqrt( Re(x)2 + Im(x)2 ) sgn(x) = x / |x| if x /= 0 = 1 if x = 0 c = |a| / sqrt(|a|2 + |b|2) s = sgn(a) * conjg(b) / sqrt(|a|2 + |b|2) When a and b are real and r /= 0, the formulas simplify to r = sgn(a)sqrt(|a|2 + |b|*2) c = a / r s = b / r the same as in SROTG when |a| > |b|. When |b| >= |a|, the sign of c and s will be different from those computed by SROTG if the signs of a and b are not the same.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
complex(kind=sp), | intent(inout) | :: | a | |||
complex(kind=sp), | intent(in) | :: | b | |||
real(kind=sp), | intent(out) | :: | c | |||
complex(kind=sp), | intent(out) | :: | s |
CSCAL scales a vector by a constant.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | ca | |||
complex(kind=sp), | intent(inout) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |
CSROT applies a plane rotation, where the cos and sin (c and s) are real and the vectors cx and cy are complex. jack dongarra, linpack, 3/11/78.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(inout) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(inout) | :: | cy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
real(kind=sp), | intent(in) | :: | c | |||
real(kind=sp), | intent(in) | :: | s |
CSSCAL scales a complex vector by a real constant.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
real(kind=sp), | intent(in) | :: | sa | |||
complex(kind=sp), | intent(inout) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |
CSWAP interchanges two vectors.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(inout) | :: | cx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=sp), | intent(inout) | :: | cy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
CSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | side | |||
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
CSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
CSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
CTBMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(inout) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |
CTBSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(inout) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |
CTPMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | ap(*) | |||
complex(kind=sp), | intent(inout) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |
CTPSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | ap(*) | |||
complex(kind=sp), | intent(inout) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |
CTRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ) where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | side | |||
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | transa | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(inout) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb |
CTRMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(inout) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |
CTRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. The matrix X is overwritten on B.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | side | |||
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | transa | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(inout) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb |
CTRSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
character(len=1), | intent(in) | :: | diag | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(inout) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx |