Diff for /rpl/lapack/blas/zgemm.f between versions 1.11 and 1.16

version 1.11, 2014/01/27 09:28:14 version 1.16, 2018/05/29 07:19:42
Line 2 Line 2
 *  *
 *  =========== DOCUMENTATION ===========  *  =========== DOCUMENTATION ===========
 *  *
 * Online html documentation available at   * Online html documentation available at
 *            http://www.netlib.org/lapack/explore-html/   *            http://www.netlib.org/lapack/explore-html/
 *  *
 *  Definition:  *  Definition:
 *  ===========  *  ===========
 *  *
 *       SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)  *       SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
 *   *
 *       .. Scalar Arguments ..  *       .. Scalar Arguments ..
 *       COMPLEX*16 ALPHA,BETA  *       COMPLEX*16 ALPHA,BETA
 *       INTEGER K,LDA,LDB,LDC,M,N  *       INTEGER K,LDA,LDB,LDC,M,N
Line 18 Line 18
 *       .. Array Arguments ..  *       .. Array Arguments ..
 *       COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)  *       COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)
 *       ..  *       ..
 *    *
 *  *
 *> \par Purpose:  *> \par Purpose:
 *  =============  *  =============
Line 97 Line 97
 *>  *>
 *> \param[in] A  *> \param[in] A
 *> \verbatim  *> \verbatim
 *>          A is COMPLEX*16 array of DIMENSION ( LDA, ka ), where ka is  *>          A is COMPLEX*16 array, dimension ( LDA, ka ), where ka is
 *>           k  when  TRANSA = 'N' or 'n',  and is  m  otherwise.  *>           k  when  TRANSA = 'N' or 'n',  and is  m  otherwise.
 *>           Before entry with  TRANSA = 'N' or 'n',  the leading  m by k  *>           Before entry with  TRANSA = 'N' or 'n',  the leading  m by k
 *>           part of the array  A  must contain the matrix  A,  otherwise  *>           part of the array  A  must contain the matrix  A,  otherwise
Line 116 Line 116
 *>  *>
 *> \param[in] B  *> \param[in] B
 *> \verbatim  *> \verbatim
 *>          B is COMPLEX*16 array of DIMENSION ( LDB, kb ), where kb is  *>          B is COMPLEX*16 array, dimension ( LDB, kb ), where kb is
 *>           n  when  TRANSB = 'N' or 'n',  and is  k  otherwise.  *>           n  when  TRANSB = 'N' or 'n',  and is  k  otherwise.
 *>           Before entry with  TRANSB = 'N' or 'n',  the leading  k by n  *>           Before entry with  TRANSB = 'N' or 'n',  the leading  k by n
 *>           part of the array  B  must contain the matrix  B,  otherwise  *>           part of the array  B  must contain the matrix  B,  otherwise
Line 142 Line 142
 *>  *>
 *> \param[in,out] C  *> \param[in,out] C
 *> \verbatim  *> \verbatim
 *>          C is COMPLEX*16 array of DIMENSION ( LDC, n ).  *>          C is COMPLEX*16 array, dimension ( LDC, N )
 *>           Before entry, the leading  m by n  part of the array  C must  *>           Before entry, the leading  m by n  part of the array  C must
 *>           contain the matrix  C,  except when  beta  is zero, in which  *>           contain the matrix  C,  except when  beta  is zero, in which
 *>           case C need not be set on entry.  *>           case C need not be set on entry.
Line 161 Line 161
 *  Authors:  *  Authors:
 *  ========  *  ========
 *  *
 *> \author Univ. of Tennessee   *> \author Univ. of Tennessee
 *> \author Univ. of California Berkeley   *> \author Univ. of California Berkeley
 *> \author Univ. of Colorado Denver   *> \author Univ. of Colorado Denver
 *> \author NAG Ltd.   *> \author NAG Ltd.
 *  *
 *> \date November 2011  *> \date December 2016
 *  *
 *> \ingroup complex16_blas_level3  *> \ingroup complex16_blas_level3
 *  *
Line 187 Line 187
 *  =====================================================================  *  =====================================================================
       SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)        SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
 *  *
 *  -- Reference BLAS level3 routine (version 3.4.0) --  *  -- Reference BLAS level3 routine (version 3.7.0) --
 *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --  *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     November 2011  *     December 2016
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       COMPLEX*16 ALPHA,BETA        COMPLEX*16 ALPHA,BETA
Line 317 Line 317
    60                 CONTINUE     60                 CONTINUE
                   END IF                    END IF
                   DO 80 L = 1,K                    DO 80 L = 1,K
                       IF (B(L,J).NE.ZERO) THEN                        TEMP = ALPHA*B(L,J)
                           TEMP = ALPHA*B(L,J)                        DO 70 I = 1,M
                           DO 70 I = 1,M                            C(I,J) = C(I,J) + TEMP*A(I,L)
                               C(I,J) = C(I,J) + TEMP*A(I,L)     70                 CONTINUE
    70                     CONTINUE  
                       END IF  
    80             CONTINUE     80             CONTINUE
    90         CONTINUE     90         CONTINUE
           ELSE IF (CONJA) THEN            ELSE IF (CONJA) THEN
Line 376 Line 374
   170                 CONTINUE    170                 CONTINUE
                   END IF                    END IF
                   DO 190 L = 1,K                    DO 190 L = 1,K
                       IF (B(J,L).NE.ZERO) THEN                        TEMP = ALPHA*DCONJG(B(J,L))
                           TEMP = ALPHA*DCONJG(B(J,L))                        DO 180 I = 1,M
                           DO 180 I = 1,M                            C(I,J) = C(I,J) + TEMP*A(I,L)
                               C(I,J) = C(I,J) + TEMP*A(I,L)    180                 CONTINUE
   180                     CONTINUE  
                       END IF  
   190             CONTINUE    190             CONTINUE
   200         CONTINUE    200         CONTINUE
           ELSE            ELSE
 *  *
 *           Form  C := alpha*A*B**T          + beta*C  *           Form  C := alpha*A*B**T + beta*C
 *  *
               DO 250 J = 1,N                DO 250 J = 1,N
                   IF (BETA.EQ.ZERO) THEN                    IF (BETA.EQ.ZERO) THEN
Line 399 Line 395
   220                 CONTINUE    220                 CONTINUE
                   END IF                    END IF
                   DO 240 L = 1,K                    DO 240 L = 1,K
                       IF (B(J,L).NE.ZERO) THEN                        TEMP = ALPHA*B(J,L)
                           TEMP = ALPHA*B(J,L)                        DO 230 I = 1,M
                           DO 230 I = 1,M                            C(I,J) = C(I,J) + TEMP*A(I,L)
                               C(I,J) = C(I,J) + TEMP*A(I,L)    230                 CONTINUE
   230                     CONTINUE  
                       END IF  
   240             CONTINUE    240             CONTINUE
   250         CONTINUE    250         CONTINUE
           END IF            END IF

Removed from v.1.11  
changed lines
  Added in v.1.16


CVSweb interface <joel.bertrand@systella.fr>