dsyr2k
C DSYR2K SOURCE BP208322 22/09/16 21:15:08 11454 *> \brief \b DSYR2K * * =========== DOCUMENTATION =========== * * Online html documentation available at * http://www.netlib.org/lapack/explore-html/ * * Definition: * =========== * * SUBROUTINE DSYR2K(UPLO,TRANS,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC) * * .. Scalar Arguments .. * REAL*8 ALPHA,BETA * INTEGER K,LDA,LDB,LDC,N * CHARACTER TRANS,UPLO * .. * .. Array Arguments .. * REAL*8 A(LDA,*),B(LDB,*),C(LDC,*) * .. * * *> \par Purpose: * ============= *> *> \verbatim *> *> DSYR2K performs one of the symmetric rank 2k operations *> *> C := alpha*A*B**T + alpha*B*A**T + beta*C, *> *> or *> *> C := alpha*A**T*B + alpha*B**T*A + beta*C, *> *> 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. *> \endverbatim * * Arguments: * ========== * *> \param[in] UPLO *> \verbatim *> UPLO is CHARACTER*1 *> On entry, UPLO specifies whether the upper or lower *> triangular part of the array C is to be referenced as *> follows: *> *> UPLO = 'U' or 'u' Only the upper triangular part of C *> is to be referenced. *> *> UPLO = 'L' or 'l' Only the lower triangular part of C *> is to be referenced. *> \endverbatim *> *> \param[in] TRANS *> \verbatim *> TRANS is CHARACTER*1 *> On entry, TRANS specifies the operation to be performed as *> follows: *> *> TRANS = 'N' or 'n' C := alpha*A*B**T + alpha*B*A**T + *> beta*C. *> *> TRANS = 'T' or 't' C := alpha*A**T*B + alpha*B**T*A + *> beta*C. *> *> TRANS = 'C' or 'c' C := alpha*A**T*B + alpha*B**T*A + *> beta*C. *> \endverbatim *> *> \param[in] N *> \verbatim *> N is INTEGER *> On entry, N specifies the order of the matrix C. N must be *> at least zero. *> \endverbatim *> *> \param[in] K *> \verbatim *> K is INTEGER *> On entry with TRANS = 'N' or 'n', K specifies the number *> of columns of the matrices A and B, and on entry with *> TRANS = 'T' or 't' or 'C' or 'c', K specifies the number *> of rows of the matrices A and B. K must be at least zero. *> \endverbatim *> *> \param[in] ALPHA *> \verbatim *> ALPHA is REAL*8. *> On entry, ALPHA specifies the scalar alpha. *> \endverbatim *> *> \param[in] A *> \verbatim *> A is REAL*8 array, dimension ( LDA, ka ), where ka is *> k when TRANS = 'N' or 'n', and is n otherwise. *> Before entry with TRANS = 'N' or 'n', the leading n by k *> part of the array A must contain the matrix A, otherwise *> the leading k by n part of the array A must contain the *> matrix A. *> \endverbatim *> *> \param[in] LDA *> \verbatim *> LDA is INTEGER *> On entry, LDA specifies the first dimension of A as declared *> in the calling (sub) program. When TRANS = 'N' or 'n' *> then LDA must be at least max( 1, n ), otherwise LDA must *> be at least max( 1, k ). *> \endverbatim *> *> \param[in] B *> \verbatim *> B is REAL*8 array, dimension ( LDB, kb ), where kb is *> k when TRANS = 'N' or 'n', and is n otherwise. *> Before entry with TRANS = 'N' or 'n', the leading n by k *> part of the array B must contain the matrix B, otherwise *> the leading k by n part of the array B must contain the *> matrix B. *> \endverbatim *> *> \param[in] LDB *> \verbatim *> LDB is INTEGER *> On entry, LDB specifies the first dimension of B as declared *> in the calling (sub) program. When TRANS = 'N' or 'n' *> then LDB must be at least max( 1, n ), otherwise LDB must *> be at least max( 1, k ). *> \endverbatim *> *> \param[in] BETA *> \verbatim *> BETA is REAL*8. *> On entry, BETA specifies the scalar beta. *> \endverbatim *> *> \param[in,out] C *> \verbatim *> C is REAL*8 array, dimension ( LDC, N ) *> Before entry with UPLO = 'U' or 'u', the leading n by n *> upper triangular part of the array C must contain the upper *> triangular part of the symmetric matrix and the strictly *> lower triangular part of C is not referenced. On exit, the *> upper triangular part of the array C is overwritten by the *> upper triangular part of the updated matrix. *> Before entry with UPLO = 'L' or 'l', the leading n by n *> lower triangular part of the array C must contain the lower *> triangular part of the symmetric matrix and the strictly *> upper triangular part of C is not referenced. On exit, the *> lower triangular part of the array C is overwritten by the *> lower triangular part of the updated matrix. *> \endverbatim *> *> \param[in] LDC *> \verbatim *> LDC is INTEGER *> On entry, LDC specifies the first dimension of C as declared *> in the calling (sub) program. LDC must be at least *> max( 1, n ). *> \endverbatim * * Authors: * ======== * *> \author Univ. of Tennessee *> \author Univ. of California Berkeley *> \author Univ. of Colorado Denver *> \author NAG Ltd. * *> \ingroup double_blas_level3 * *> \par Further Details: * ===================== *> *> \verbatim *> *> Level 3 Blas routine. *> *> *> -- Written on 8-February-1989. *> Jack Dongarra, Argonne National Laboratory. *> Iain Duff, AERE Harwell. *> Jeremy Du Croz, Numerical Algorithms Group Ltd. *> Sven Hammarling, Numerical Algorithms Group Ltd. *> \endverbatim *> * ===================================================================== * * -- Reference BLAS level3 routine -- * -- Reference BLAS is a software package provided by Univ. of Tennessee, -- * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- * * .. Scalar Arguments .. INTEGER K,LDA,LDB,LDC,N CHARACTER TRANS,UPLO * .. * .. Array Arguments .. REAL*8 A(LDA,*),B(LDB,*),C(LDC,*) * .. * * ===================================================================== * * .. External Functions .. LOGICAL LSAME EXTERNAL LSAME * .. * .. External Subroutines .. EXTERNAL XERBLA * .. * .. Intrinsic Functions .. * INTRINSIC MAX * .. * .. Local Scalars .. REAL*8 TEMP1,TEMP2 INTEGER I,INFO,J,L,NROWA LOGICAL UPPER * .. * .. Parameters .. * .. * * Test the input parameters. * NROWA = N ELSE NROWA = K END IF * INFO = 0 INFO = 1 INFO = 2 ELSE IF (N.LT.0) THEN INFO = 3 ELSE IF (K.LT.0) THEN INFO = 4 ELSE IF (LDA.LT.MAX(1,NROWA)) THEN INFO = 7 ELSE IF (LDB.LT.MAX(1,NROWA)) THEN INFO = 9 ELSE IF (LDC.LT.MAX(1,N)) THEN INFO = 12 END IF IF (INFO.NE.0) THEN RETURN END IF * * Quick return if possible. * + (K.EQ.0)).AND. (BETA.EQ.ONE))) RETURN * * And when alpha.eq.zero. * IF (UPPER) THEN DO 20 J = 1,N DO 10 I = 1,J 10 CONTINUE 20 CONTINUE ELSE DO 40 J = 1,N DO 30 I = 1,J C(I,J) = BETA*C(I,J) 30 CONTINUE 40 CONTINUE END IF ELSE DO 60 J = 1,N DO 50 I = J,N 50 CONTINUE 60 CONTINUE ELSE DO 80 J = 1,N DO 70 I = J,N C(I,J) = BETA*C(I,J) 70 CONTINUE 80 CONTINUE END IF END IF RETURN END IF * * Start the operations. * * * Form C := alpha*A*B**T + alpha*B*A**T + C. * IF (UPPER) THEN DO 130 J = 1,N DO 90 I = 1,J 90 CONTINUE ELSE IF (BETA.NE.ONE) THEN DO 100 I = 1,J C(I,J) = BETA*C(I,J) 100 CONTINUE END IF DO 120 L = 1,K DO 110 I = 1,J C(I,J) = C(I,J) + A(I,L)*TEMP1 + + B(I,L)*TEMP2 110 CONTINUE END IF 120 CONTINUE 130 CONTINUE ELSE DO 180 J = 1,N DO 140 I = J,N 140 CONTINUE ELSE IF (BETA.NE.ONE) THEN DO 150 I = J,N C(I,J) = BETA*C(I,J) 150 CONTINUE END IF DO 170 L = 1,K DO 160 I = J,N C(I,J) = C(I,J) + A(I,L)*TEMP1 + + B(I,L)*TEMP2 160 CONTINUE END IF 170 CONTINUE 180 CONTINUE END IF ELSE * * Form C := alpha*A**T*B + alpha*B**T*A + C. * IF (UPPER) THEN DO 210 J = 1,N DO 200 I = 1,J TEMP1 = ZERO TEMP2 = ZERO DO 190 L = 1,K TEMP1 = TEMP1 + A(L,I)*B(L,J) TEMP2 = TEMP2 + B(L,I)*A(L,J) 190 CONTINUE ELSE END IF 200 CONTINUE 210 CONTINUE ELSE DO 240 J = 1,N DO 230 I = J,N TEMP1 = ZERO TEMP2 = ZERO DO 220 L = 1,K TEMP1 = TEMP1 + A(L,I)*B(L,J) TEMP2 = TEMP2 + B(L,I)*A(L,J) 220 CONTINUE ELSE END IF 230 CONTINUE 240 CONTINUE END IF END IF * RETURN * * End of DSYR2K * END
© Cast3M 2003 - Tous droits réservés.
Mentions légales