Annotation of rpl/lapack/blas/zgemm.f, revision 1.12

1.8       bertrand    1: *> \brief \b ZGEMM
                      2: *
                      3: *  =========== DOCUMENTATION ===========
                      4: *
                      5: * Online html documentation available at 
                      6: *            http://www.netlib.org/lapack/explore-html/ 
                      7: *
                      8: *  Definition:
                      9: *  ===========
                     10: *
                     11: *       SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
                     12: * 
                     13: *       .. Scalar Arguments ..
                     14: *       COMPLEX*16 ALPHA,BETA
                     15: *       INTEGER K,LDA,LDB,LDC,M,N
                     16: *       CHARACTER TRANSA,TRANSB
                     17: *       ..
                     18: *       .. Array Arguments ..
                     19: *       COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)
                     20: *       ..
                     21: *  
                     22: *
                     23: *> \par Purpose:
                     24: *  =============
                     25: *>
                     26: *> \verbatim
                     27: *>
                     28: *> ZGEMM  performs one of the matrix-matrix operations
                     29: *>
                     30: *>    C := alpha*op( A )*op( B ) + beta*C,
                     31: *>
                     32: *> where  op( X ) is one of
                     33: *>
                     34: *>    op( X ) = X   or   op( X ) = X**T   or   op( X ) = X**H,
                     35: *>
                     36: *> alpha and beta are scalars, and A, B and C are matrices, with op( A )
                     37: *> an m by k matrix,  op( B )  a  k by n matrix and  C an m by n matrix.
                     38: *> \endverbatim
                     39: *
                     40: *  Arguments:
                     41: *  ==========
                     42: *
                     43: *> \param[in] TRANSA
                     44: *> \verbatim
                     45: *>          TRANSA is CHARACTER*1
                     46: *>           On entry, TRANSA specifies the form of op( A ) to be used in
                     47: *>           the matrix multiplication as follows:
                     48: *>
                     49: *>              TRANSA = 'N' or 'n',  op( A ) = A.
                     50: *>
                     51: *>              TRANSA = 'T' or 't',  op( A ) = A**T.
                     52: *>
                     53: *>              TRANSA = 'C' or 'c',  op( A ) = A**H.
                     54: *> \endverbatim
                     55: *>
                     56: *> \param[in] TRANSB
                     57: *> \verbatim
                     58: *>          TRANSB is CHARACTER*1
                     59: *>           On entry, TRANSB specifies the form of op( B ) to be used in
                     60: *>           the matrix multiplication as follows:
                     61: *>
                     62: *>              TRANSB = 'N' or 'n',  op( B ) = B.
                     63: *>
                     64: *>              TRANSB = 'T' or 't',  op( B ) = B**T.
                     65: *>
                     66: *>              TRANSB = 'C' or 'c',  op( B ) = B**H.
                     67: *> \endverbatim
                     68: *>
                     69: *> \param[in] M
                     70: *> \verbatim
                     71: *>          M is INTEGER
                     72: *>           On entry,  M  specifies  the number  of rows  of the  matrix
                     73: *>           op( A )  and of the  matrix  C.  M  must  be at least  zero.
                     74: *> \endverbatim
                     75: *>
                     76: *> \param[in] N
                     77: *> \verbatim
                     78: *>          N is INTEGER
                     79: *>           On entry,  N  specifies the number  of columns of the matrix
                     80: *>           op( B ) and the number of columns of the matrix C. N must be
                     81: *>           at least zero.
                     82: *> \endverbatim
                     83: *>
                     84: *> \param[in] K
                     85: *> \verbatim
                     86: *>          K is INTEGER
                     87: *>           On entry,  K  specifies  the number of columns of the matrix
                     88: *>           op( A ) and the number of rows of the matrix op( B ). K must
                     89: *>           be at least  zero.
                     90: *> \endverbatim
                     91: *>
                     92: *> \param[in] ALPHA
                     93: *> \verbatim
                     94: *>          ALPHA is COMPLEX*16
                     95: *>           On entry, ALPHA specifies the scalar alpha.
                     96: *> \endverbatim
                     97: *>
                     98: *> \param[in] A
                     99: *> \verbatim
                    100: *>          A is COMPLEX*16 array of DIMENSION ( LDA, ka ), where ka is
                    101: *>           k  when  TRANSA = 'N' or 'n',  and is  m  otherwise.
                    102: *>           Before entry with  TRANSA = 'N' or 'n',  the leading  m by k
                    103: *>           part of the array  A  must contain the matrix  A,  otherwise
                    104: *>           the leading  k by m  part of the array  A  must contain  the
                    105: *>           matrix A.
                    106: *> \endverbatim
                    107: *>
                    108: *> \param[in] LDA
                    109: *> \verbatim
                    110: *>          LDA is INTEGER
                    111: *>           On entry, LDA specifies the first dimension of A as declared
                    112: *>           in the calling (sub) program. When  TRANSA = 'N' or 'n' then
                    113: *>           LDA must be at least  max( 1, m ), otherwise  LDA must be at
                    114: *>           least  max( 1, k ).
                    115: *> \endverbatim
                    116: *>
                    117: *> \param[in] B
                    118: *> \verbatim
                    119: *>          B is COMPLEX*16 array of DIMENSION ( LDB, kb ), where kb is
                    120: *>           n  when  TRANSB = 'N' or 'n',  and is  k  otherwise.
                    121: *>           Before entry with  TRANSB = 'N' or 'n',  the leading  k by n
                    122: *>           part of the array  B  must contain the matrix  B,  otherwise
                    123: *>           the leading  n by k  part of the array  B  must contain  the
                    124: *>           matrix B.
                    125: *> \endverbatim
                    126: *>
                    127: *> \param[in] LDB
                    128: *> \verbatim
                    129: *>          LDB is INTEGER
                    130: *>           On entry, LDB specifies the first dimension of B as declared
                    131: *>           in the calling (sub) program. When  TRANSB = 'N' or 'n' then
                    132: *>           LDB must be at least  max( 1, k ), otherwise  LDB must be at
                    133: *>           least  max( 1, n ).
                    134: *> \endverbatim
                    135: *>
                    136: *> \param[in] BETA
                    137: *> \verbatim
                    138: *>          BETA is COMPLEX*16
                    139: *>           On entry,  BETA  specifies the scalar  beta.  When  BETA  is
                    140: *>           supplied as zero then C need not be set on input.
                    141: *> \endverbatim
                    142: *>
                    143: *> \param[in,out] C
                    144: *> \verbatim
                    145: *>          C is COMPLEX*16 array of DIMENSION ( LDC, n ).
                    146: *>           Before entry, the leading  m by n  part of the array  C must
                    147: *>           contain the matrix  C,  except when  beta  is zero, in which
                    148: *>           case C need not be set on entry.
                    149: *>           On exit, the array  C  is overwritten by the  m by n  matrix
                    150: *>           ( alpha*op( A )*op( B ) + beta*C ).
                    151: *> \endverbatim
                    152: *>
                    153: *> \param[in] LDC
                    154: *> \verbatim
                    155: *>          LDC is INTEGER
                    156: *>           On entry, LDC specifies the first dimension of C as declared
                    157: *>           in  the  calling  (sub)  program.   LDC  must  be  at  least
                    158: *>           max( 1, m ).
                    159: *> \endverbatim
                    160: *
                    161: *  Authors:
                    162: *  ========
                    163: *
                    164: *> \author Univ. of Tennessee 
                    165: *> \author Univ. of California Berkeley 
                    166: *> \author Univ. of Colorado Denver 
                    167: *> \author NAG Ltd. 
                    168: *
1.12    ! bertrand  169: *> \date November 2015
1.8       bertrand  170: *
                    171: *> \ingroup complex16_blas_level3
                    172: *
                    173: *> \par Further Details:
                    174: *  =====================
                    175: *>
                    176: *> \verbatim
                    177: *>
                    178: *>  Level 3 Blas routine.
                    179: *>
                    180: *>  -- Written on 8-February-1989.
                    181: *>     Jack Dongarra, Argonne National Laboratory.
                    182: *>     Iain Duff, AERE Harwell.
                    183: *>     Jeremy Du Croz, Numerical Algorithms Group Ltd.
                    184: *>     Sven Hammarling, Numerical Algorithms Group Ltd.
                    185: *> \endverbatim
                    186: *>
                    187: *  =====================================================================
1.1       bertrand  188:       SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
1.8       bertrand  189: *
1.12    ! bertrand  190: *  -- Reference BLAS level3 routine (version 3.6.0) --
1.8       bertrand  191: *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --
                    192: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
1.12    ! bertrand  193: *     November 2015
1.8       bertrand  194: *
1.1       bertrand  195: *     .. Scalar Arguments ..
1.8       bertrand  196:       COMPLEX*16 ALPHA,BETA
1.1       bertrand  197:       INTEGER K,LDA,LDB,LDC,M,N
                    198:       CHARACTER TRANSA,TRANSB
                    199: *     ..
                    200: *     .. Array Arguments ..
1.8       bertrand  201:       COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)
1.1       bertrand  202: *     ..
                    203: *
                    204: *  =====================================================================
                    205: *
                    206: *     .. External Functions ..
                    207:       LOGICAL LSAME
                    208:       EXTERNAL LSAME
                    209: *     ..
                    210: *     .. External Subroutines ..
                    211:       EXTERNAL XERBLA
                    212: *     ..
                    213: *     .. Intrinsic Functions ..
                    214:       INTRINSIC DCONJG,MAX
                    215: *     ..
                    216: *     .. Local Scalars ..
1.8       bertrand  217:       COMPLEX*16 TEMP
1.1       bertrand  218:       INTEGER I,INFO,J,L,NCOLA,NROWA,NROWB
                    219:       LOGICAL CONJA,CONJB,NOTA,NOTB
                    220: *     ..
                    221: *     .. Parameters ..
1.8       bertrand  222:       COMPLEX*16 ONE
1.1       bertrand  223:       PARAMETER (ONE= (1.0D+0,0.0D+0))
1.8       bertrand  224:       COMPLEX*16 ZERO
1.1       bertrand  225:       PARAMETER (ZERO= (0.0D+0,0.0D+0))
                    226: *     ..
                    227: *
                    228: *     Set  NOTA  and  NOTB  as  true if  A  and  B  respectively are not
                    229: *     conjugated or transposed, set  CONJA and CONJB  as true if  A  and
                    230: *     B  respectively are to be  transposed but  not conjugated  and set
                    231: *     NROWA, NCOLA and  NROWB  as the number of rows and  columns  of  A
                    232: *     and the number of rows of  B  respectively.
                    233: *
                    234:       NOTA = LSAME(TRANSA,'N')
                    235:       NOTB = LSAME(TRANSB,'N')
                    236:       CONJA = LSAME(TRANSA,'C')
                    237:       CONJB = LSAME(TRANSB,'C')
                    238:       IF (NOTA) THEN
                    239:           NROWA = M
                    240:           NCOLA = K
                    241:       ELSE
                    242:           NROWA = K
                    243:           NCOLA = M
                    244:       END IF
                    245:       IF (NOTB) THEN
                    246:           NROWB = K
                    247:       ELSE
                    248:           NROWB = N
                    249:       END IF
                    250: *
                    251: *     Test the input parameters.
                    252: *
                    253:       INFO = 0
                    254:       IF ((.NOT.NOTA) .AND. (.NOT.CONJA) .AND.
                    255:      +    (.NOT.LSAME(TRANSA,'T'))) THEN
                    256:           INFO = 1
                    257:       ELSE IF ((.NOT.NOTB) .AND. (.NOT.CONJB) .AND.
                    258:      +         (.NOT.LSAME(TRANSB,'T'))) THEN
                    259:           INFO = 2
                    260:       ELSE IF (M.LT.0) THEN
                    261:           INFO = 3
                    262:       ELSE IF (N.LT.0) THEN
                    263:           INFO = 4
                    264:       ELSE IF (K.LT.0) THEN
                    265:           INFO = 5
                    266:       ELSE IF (LDA.LT.MAX(1,NROWA)) THEN
                    267:           INFO = 8
                    268:       ELSE IF (LDB.LT.MAX(1,NROWB)) THEN
                    269:           INFO = 10
                    270:       ELSE IF (LDC.LT.MAX(1,M)) THEN
                    271:           INFO = 13
                    272:       END IF
                    273:       IF (INFO.NE.0) THEN
                    274:           CALL XERBLA('ZGEMM ',INFO)
                    275:           RETURN
                    276:       END IF
                    277: *
                    278: *     Quick return if possible.
                    279: *
                    280:       IF ((M.EQ.0) .OR. (N.EQ.0) .OR.
                    281:      +    (((ALPHA.EQ.ZERO).OR. (K.EQ.0)).AND. (BETA.EQ.ONE))) RETURN
                    282: *
                    283: *     And when  alpha.eq.zero.
                    284: *
                    285:       IF (ALPHA.EQ.ZERO) THEN
                    286:           IF (BETA.EQ.ZERO) THEN
                    287:               DO 20 J = 1,N
                    288:                   DO 10 I = 1,M
                    289:                       C(I,J) = ZERO
                    290:    10             CONTINUE
                    291:    20         CONTINUE
                    292:           ELSE
                    293:               DO 40 J = 1,N
                    294:                   DO 30 I = 1,M
                    295:                       C(I,J) = BETA*C(I,J)
                    296:    30             CONTINUE
                    297:    40         CONTINUE
                    298:           END IF
                    299:           RETURN
                    300:       END IF
                    301: *
                    302: *     Start the operations.
                    303: *
                    304:       IF (NOTB) THEN
                    305:           IF (NOTA) THEN
                    306: *
                    307: *           Form  C := alpha*A*B + beta*C.
                    308: *
                    309:               DO 90 J = 1,N
                    310:                   IF (BETA.EQ.ZERO) THEN
                    311:                       DO 50 I = 1,M
                    312:                           C(I,J) = ZERO
                    313:    50                 CONTINUE
                    314:                   ELSE IF (BETA.NE.ONE) THEN
                    315:                       DO 60 I = 1,M
                    316:                           C(I,J) = BETA*C(I,J)
                    317:    60                 CONTINUE
                    318:                   END IF
                    319:                   DO 80 L = 1,K
1.12    ! bertrand  320:                       TEMP = ALPHA*B(L,J)
        !           321:                       DO 70 I = 1,M
        !           322:                           C(I,J) = C(I,J) + TEMP*A(I,L)
        !           323:    70                 CONTINUE
1.1       bertrand  324:    80             CONTINUE
                    325:    90         CONTINUE
                    326:           ELSE IF (CONJA) THEN
                    327: *
1.7       bertrand  328: *           Form  C := alpha*A**H*B + beta*C.
1.1       bertrand  329: *
                    330:               DO 120 J = 1,N
                    331:                   DO 110 I = 1,M
                    332:                       TEMP = ZERO
                    333:                       DO 100 L = 1,K
                    334:                           TEMP = TEMP + DCONJG(A(L,I))*B(L,J)
                    335:   100                 CONTINUE
                    336:                       IF (BETA.EQ.ZERO) THEN
                    337:                           C(I,J) = ALPHA*TEMP
                    338:                       ELSE
                    339:                           C(I,J) = ALPHA*TEMP + BETA*C(I,J)
                    340:                       END IF
                    341:   110             CONTINUE
                    342:   120         CONTINUE
                    343:           ELSE
                    344: *
1.7       bertrand  345: *           Form  C := alpha*A**T*B + beta*C
1.1       bertrand  346: *
                    347:               DO 150 J = 1,N
                    348:                   DO 140 I = 1,M
                    349:                       TEMP = ZERO
                    350:                       DO 130 L = 1,K
                    351:                           TEMP = TEMP + A(L,I)*B(L,J)
                    352:   130                 CONTINUE
                    353:                       IF (BETA.EQ.ZERO) THEN
                    354:                           C(I,J) = ALPHA*TEMP
                    355:                       ELSE
                    356:                           C(I,J) = ALPHA*TEMP + BETA*C(I,J)
                    357:                       END IF
                    358:   140             CONTINUE
                    359:   150         CONTINUE
                    360:           END IF
                    361:       ELSE IF (NOTA) THEN
                    362:           IF (CONJB) THEN
                    363: *
1.7       bertrand  364: *           Form  C := alpha*A*B**H + beta*C.
1.1       bertrand  365: *
                    366:               DO 200 J = 1,N
                    367:                   IF (BETA.EQ.ZERO) THEN
                    368:                       DO 160 I = 1,M
                    369:                           C(I,J) = ZERO
                    370:   160                 CONTINUE
                    371:                   ELSE IF (BETA.NE.ONE) THEN
                    372:                       DO 170 I = 1,M
                    373:                           C(I,J) = BETA*C(I,J)
                    374:   170                 CONTINUE
                    375:                   END IF
                    376:                   DO 190 L = 1,K
1.12    ! bertrand  377:                       TEMP = ALPHA*DCONJG(B(J,L))
        !           378:                       DO 180 I = 1,M
        !           379:                           C(I,J) = C(I,J) + TEMP*A(I,L)
        !           380:   180                 CONTINUE
1.1       bertrand  381:   190             CONTINUE
                    382:   200         CONTINUE
                    383:           ELSE
                    384: *
1.12    ! bertrand  385: *           Form  C := alpha*A*B**T + beta*C
1.1       bertrand  386: *
                    387:               DO 250 J = 1,N
                    388:                   IF (BETA.EQ.ZERO) THEN
                    389:                       DO 210 I = 1,M
                    390:                           C(I,J) = ZERO
                    391:   210                 CONTINUE
                    392:                   ELSE IF (BETA.NE.ONE) THEN
                    393:                       DO 220 I = 1,M
                    394:                           C(I,J) = BETA*C(I,J)
                    395:   220                 CONTINUE
                    396:                   END IF
                    397:                   DO 240 L = 1,K
1.12    ! bertrand  398:                       TEMP = ALPHA*B(J,L)
        !           399:                       DO 230 I = 1,M
        !           400:                           C(I,J) = C(I,J) + TEMP*A(I,L)
        !           401:   230                 CONTINUE
1.1       bertrand  402:   240             CONTINUE
                    403:   250         CONTINUE
                    404:           END IF
                    405:       ELSE IF (CONJA) THEN
                    406:           IF (CONJB) THEN
                    407: *
1.7       bertrand  408: *           Form  C := alpha*A**H*B**H + beta*C.
1.1       bertrand  409: *
                    410:               DO 280 J = 1,N
                    411:                   DO 270 I = 1,M
                    412:                       TEMP = ZERO
                    413:                       DO 260 L = 1,K
                    414:                           TEMP = TEMP + DCONJG(A(L,I))*DCONJG(B(J,L))
                    415:   260                 CONTINUE
                    416:                       IF (BETA.EQ.ZERO) THEN
                    417:                           C(I,J) = ALPHA*TEMP
                    418:                       ELSE
                    419:                           C(I,J) = ALPHA*TEMP + BETA*C(I,J)
                    420:                       END IF
                    421:   270             CONTINUE
                    422:   280         CONTINUE
                    423:           ELSE
                    424: *
1.7       bertrand  425: *           Form  C := alpha*A**H*B**T + beta*C
1.1       bertrand  426: *
                    427:               DO 310 J = 1,N
                    428:                   DO 300 I = 1,M
                    429:                       TEMP = ZERO
                    430:                       DO 290 L = 1,K
                    431:                           TEMP = TEMP + DCONJG(A(L,I))*B(J,L)
                    432:   290                 CONTINUE
                    433:                       IF (BETA.EQ.ZERO) THEN
                    434:                           C(I,J) = ALPHA*TEMP
                    435:                       ELSE
                    436:                           C(I,J) = ALPHA*TEMP + BETA*C(I,J)
                    437:                       END IF
                    438:   300             CONTINUE
                    439:   310         CONTINUE
                    440:           END IF
                    441:       ELSE
                    442:           IF (CONJB) THEN
                    443: *
1.7       bertrand  444: *           Form  C := alpha*A**T*B**H + beta*C
1.1       bertrand  445: *
                    446:               DO 340 J = 1,N
                    447:                   DO 330 I = 1,M
                    448:                       TEMP = ZERO
                    449:                       DO 320 L = 1,K
                    450:                           TEMP = TEMP + A(L,I)*DCONJG(B(J,L))
                    451:   320                 CONTINUE
                    452:                       IF (BETA.EQ.ZERO) THEN
                    453:                           C(I,J) = ALPHA*TEMP
                    454:                       ELSE
                    455:                           C(I,J) = ALPHA*TEMP + BETA*C(I,J)
                    456:                       END IF
                    457:   330             CONTINUE
                    458:   340         CONTINUE
                    459:           ELSE
                    460: *
1.7       bertrand  461: *           Form  C := alpha*A**T*B**T + beta*C
1.1       bertrand  462: *
                    463:               DO 370 J = 1,N
                    464:                   DO 360 I = 1,M
                    465:                       TEMP = ZERO
                    466:                       DO 350 L = 1,K
                    467:                           TEMP = TEMP + A(L,I)*B(J,L)
                    468:   350                 CONTINUE
                    469:                       IF (BETA.EQ.ZERO) THEN
                    470:                           C(I,J) = ALPHA*TEMP
                    471:                       ELSE
                    472:                           C(I,J) = ALPHA*TEMP + BETA*C(I,J)
                    473:                       END IF
                    474:   360             CONTINUE
                    475:   370         CONTINUE
                    476:           END IF
                    477:       END IF
                    478: *
                    479:       RETURN
                    480: *
                    481: *     End of ZGEMM .
                    482: *
                    483:       END

CVSweb interface <joel.bertrand@systella.fr>