Annotation of rpl/lapack/lapack/zlasr.f, revision 1.19

1.12      bertrand    1: *> \brief \b ZLASR applies a sequence of plane rotations to a general rectangular matrix.
1.9       bertrand    2: *
                      3: *  =========== DOCUMENTATION ===========
                      4: *
1.16      bertrand    5: * Online html documentation available at
                      6: *            http://www.netlib.org/lapack/explore-html/
1.9       bertrand    7: *
                      8: *> \htmlonly
1.16      bertrand    9: *> Download ZLASR + dependencies
                     10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlasr.f">
                     11: *> [TGZ]</a>
                     12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlasr.f">
                     13: *> [ZIP]</a>
                     14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlasr.f">
1.9       bertrand   15: *> [TXT]</a>
1.16      bertrand   16: *> \endhtmlonly
1.9       bertrand   17: *
                     18: *  Definition:
                     19: *  ===========
                     20: *
                     21: *       SUBROUTINE ZLASR( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA )
1.16      bertrand   22: *
1.9       bertrand   23: *       .. Scalar Arguments ..
                     24: *       CHARACTER          DIRECT, PIVOT, SIDE
                     25: *       INTEGER            LDA, M, N
                     26: *       ..
                     27: *       .. Array Arguments ..
                     28: *       DOUBLE PRECISION   C( * ), S( * )
                     29: *       COMPLEX*16         A( LDA, * )
                     30: *       ..
1.16      bertrand   31: *
1.9       bertrand   32: *
                     33: *> \par Purpose:
                     34: *  =============
                     35: *>
                     36: *> \verbatim
                     37: *>
                     38: *> ZLASR applies a sequence of real plane rotations to a complex matrix
                     39: *> A, from either the left or the right.
                     40: *>
                     41: *> When SIDE = 'L', the transformation takes the form
                     42: *>
                     43: *>    A := P*A
                     44: *>
                     45: *> and when SIDE = 'R', the transformation takes the form
                     46: *>
                     47: *>    A := A*P**T
                     48: *>
                     49: *> where P is an orthogonal matrix consisting of a sequence of z plane
                     50: *> rotations, with z = M when SIDE = 'L' and z = N when SIDE = 'R',
                     51: *> and P**T is the transpose of P.
1.16      bertrand   52: *>
1.9       bertrand   53: *> When DIRECT = 'F' (Forward sequence), then
1.16      bertrand   54: *>
1.9       bertrand   55: *>    P = P(z-1) * ... * P(2) * P(1)
1.16      bertrand   56: *>
1.9       bertrand   57: *> and when DIRECT = 'B' (Backward sequence), then
1.16      bertrand   58: *>
1.9       bertrand   59: *>    P = P(1) * P(2) * ... * P(z-1)
1.16      bertrand   60: *>
1.9       bertrand   61: *> where P(k) is a plane rotation matrix defined by the 2-by-2 rotation
1.16      bertrand   62: *>
1.9       bertrand   63: *>    R(k) = (  c(k)  s(k) )
                     64: *>         = ( -s(k)  c(k) ).
1.16      bertrand   65: *>
1.9       bertrand   66: *> When PIVOT = 'V' (Variable pivot), the rotation is performed
                     67: *> for the plane (k,k+1), i.e., P(k) has the form
1.16      bertrand   68: *>
1.9       bertrand   69: *>    P(k) = (  1                                            )
                     70: *>           (       ...                                     )
                     71: *>           (              1                                )
                     72: *>           (                   c(k)  s(k)                  )
                     73: *>           (                  -s(k)  c(k)                  )
                     74: *>           (                                1              )
                     75: *>           (                                     ...       )
                     76: *>           (                                            1  )
1.16      bertrand   77: *>
1.9       bertrand   78: *> where R(k) appears as a rank-2 modification to the identity matrix in
                     79: *> rows and columns k and k+1.
1.16      bertrand   80: *>
1.9       bertrand   81: *> When PIVOT = 'T' (Top pivot), the rotation is performed for the
                     82: *> plane (1,k+1), so P(k) has the form
1.16      bertrand   83: *>
1.9       bertrand   84: *>    P(k) = (  c(k)                    s(k)                 )
                     85: *>           (         1                                     )
                     86: *>           (              ...                              )
                     87: *>           (                     1                         )
                     88: *>           ( -s(k)                    c(k)                 )
                     89: *>           (                                 1             )
                     90: *>           (                                      ...      )
                     91: *>           (                                             1 )
1.16      bertrand   92: *>
1.9       bertrand   93: *> where R(k) appears in rows and columns 1 and k+1.
1.16      bertrand   94: *>
1.9       bertrand   95: *> Similarly, when PIVOT = 'B' (Bottom pivot), the rotation is
                     96: *> performed for the plane (k,z), giving P(k) the form
1.16      bertrand   97: *>
1.9       bertrand   98: *>    P(k) = ( 1                                             )
                     99: *>           (      ...                                      )
                    100: *>           (             1                                 )
                    101: *>           (                  c(k)                    s(k) )
                    102: *>           (                         1                     )
                    103: *>           (                              ...              )
                    104: *>           (                                     1         )
                    105: *>           (                 -s(k)                    c(k) )
1.16      bertrand  106: *>
1.9       bertrand  107: *> where R(k) appears in rows and columns k and z.  The rotations are
                    108: *> performed without ever forming P(k) explicitly.
                    109: *> \endverbatim
                    110: *
                    111: *  Arguments:
                    112: *  ==========
                    113: *
                    114: *> \param[in] SIDE
                    115: *> \verbatim
                    116: *>          SIDE is CHARACTER*1
                    117: *>          Specifies whether the plane rotation matrix P is applied to
                    118: *>          A on the left or the right.
                    119: *>          = 'L':  Left, compute A := P*A
                    120: *>          = 'R':  Right, compute A:= A*P**T
                    121: *> \endverbatim
                    122: *>
                    123: *> \param[in] PIVOT
                    124: *> \verbatim
                    125: *>          PIVOT is CHARACTER*1
                    126: *>          Specifies the plane for which P(k) is a plane rotation
                    127: *>          matrix.
                    128: *>          = 'V':  Variable pivot, the plane (k,k+1)
                    129: *>          = 'T':  Top pivot, the plane (1,k+1)
                    130: *>          = 'B':  Bottom pivot, the plane (k,z)
                    131: *> \endverbatim
                    132: *>
                    133: *> \param[in] DIRECT
                    134: *> \verbatim
                    135: *>          DIRECT is CHARACTER*1
                    136: *>          Specifies whether P is a forward or backward sequence of
                    137: *>          plane rotations.
                    138: *>          = 'F':  Forward, P = P(z-1)*...*P(2)*P(1)
                    139: *>          = 'B':  Backward, P = P(1)*P(2)*...*P(z-1)
                    140: *> \endverbatim
                    141: *>
                    142: *> \param[in] M
                    143: *> \verbatim
                    144: *>          M is INTEGER
                    145: *>          The number of rows of the matrix A.  If m <= 1, an immediate
                    146: *>          return is effected.
                    147: *> \endverbatim
                    148: *>
                    149: *> \param[in] N
                    150: *> \verbatim
                    151: *>          N is INTEGER
                    152: *>          The number of columns of the matrix A.  If n <= 1, an
                    153: *>          immediate return is effected.
                    154: *> \endverbatim
                    155: *>
                    156: *> \param[in] C
                    157: *> \verbatim
                    158: *>          C is DOUBLE PRECISION array, dimension
                    159: *>                  (M-1) if SIDE = 'L'
                    160: *>                  (N-1) if SIDE = 'R'
                    161: *>          The cosines c(k) of the plane rotations.
                    162: *> \endverbatim
                    163: *>
                    164: *> \param[in] S
                    165: *> \verbatim
                    166: *>          S is DOUBLE PRECISION array, dimension
                    167: *>                  (M-1) if SIDE = 'L'
                    168: *>                  (N-1) if SIDE = 'R'
                    169: *>          The sines s(k) of the plane rotations.  The 2-by-2 plane
                    170: *>          rotation part of the matrix P(k), R(k), has the form
                    171: *>          R(k) = (  c(k)  s(k) )
                    172: *>                 ( -s(k)  c(k) ).
                    173: *> \endverbatim
                    174: *>
                    175: *> \param[in,out] A
                    176: *> \verbatim
                    177: *>          A is COMPLEX*16 array, dimension (LDA,N)
                    178: *>          The M-by-N matrix A.  On exit, A is overwritten by P*A if
                    179: *>          SIDE = 'R' or by A*P**T if SIDE = 'L'.
                    180: *> \endverbatim
                    181: *>
                    182: *> \param[in] LDA
                    183: *> \verbatim
                    184: *>          LDA is INTEGER
                    185: *>          The leading dimension of the array A.  LDA >= max(1,M).
                    186: *> \endverbatim
                    187: *
                    188: *  Authors:
                    189: *  ========
                    190: *
1.16      bertrand  191: *> \author Univ. of Tennessee
                    192: *> \author Univ. of California Berkeley
                    193: *> \author Univ. of Colorado Denver
                    194: *> \author NAG Ltd.
1.9       bertrand  195: *
                    196: *> \ingroup complex16OTHERauxiliary
                    197: *
                    198: *  =====================================================================
1.1       bertrand  199:       SUBROUTINE ZLASR( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA )
                    200: *
1.19    ! bertrand  201: *  -- LAPACK auxiliary routine --
1.1       bertrand  202: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                    203: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
                    204: *
                    205: *     .. Scalar Arguments ..
                    206:       CHARACTER          DIRECT, PIVOT, SIDE
                    207:       INTEGER            LDA, M, N
                    208: *     ..
                    209: *     .. Array Arguments ..
                    210:       DOUBLE PRECISION   C( * ), S( * )
                    211:       COMPLEX*16         A( LDA, * )
                    212: *     ..
                    213: *
                    214: *  =====================================================================
                    215: *
                    216: *     .. Parameters ..
                    217:       DOUBLE PRECISION   ONE, ZERO
                    218:       PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
                    219: *     ..
                    220: *     .. Local Scalars ..
                    221:       INTEGER            I, INFO, J
                    222:       DOUBLE PRECISION   CTEMP, STEMP
                    223:       COMPLEX*16         TEMP
                    224: *     ..
                    225: *     .. Intrinsic Functions ..
                    226:       INTRINSIC          MAX
                    227: *     ..
                    228: *     .. External Functions ..
                    229:       LOGICAL            LSAME
                    230:       EXTERNAL           LSAME
                    231: *     ..
                    232: *     .. External Subroutines ..
                    233:       EXTERNAL           XERBLA
                    234: *     ..
                    235: *     .. Executable Statements ..
                    236: *
                    237: *     Test the input parameters
                    238: *
                    239:       INFO = 0
                    240:       IF( .NOT.( LSAME( SIDE, 'L' ) .OR. LSAME( SIDE, 'R' ) ) ) THEN
                    241:          INFO = 1
                    242:       ELSE IF( .NOT.( LSAME( PIVOT, 'V' ) .OR. LSAME( PIVOT,
                    243:      $         'T' ) .OR. LSAME( PIVOT, 'B' ) ) ) THEN
                    244:          INFO = 2
                    245:       ELSE IF( .NOT.( LSAME( DIRECT, 'F' ) .OR. LSAME( DIRECT, 'B' ) ) )
                    246:      $          THEN
                    247:          INFO = 3
                    248:       ELSE IF( M.LT.0 ) THEN
                    249:          INFO = 4
                    250:       ELSE IF( N.LT.0 ) THEN
                    251:          INFO = 5
                    252:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
                    253:          INFO = 9
                    254:       END IF
                    255:       IF( INFO.NE.0 ) THEN
                    256:          CALL XERBLA( 'ZLASR ', INFO )
                    257:          RETURN
                    258:       END IF
                    259: *
                    260: *     Quick return if possible
                    261: *
                    262:       IF( ( M.EQ.0 ) .OR. ( N.EQ.0 ) )
                    263:      $   RETURN
                    264:       IF( LSAME( SIDE, 'L' ) ) THEN
                    265: *
                    266: *        Form  P * A
                    267: *
                    268:          IF( LSAME( PIVOT, 'V' ) ) THEN
                    269:             IF( LSAME( DIRECT, 'F' ) ) THEN
                    270:                DO 20 J = 1, M - 1
                    271:                   CTEMP = C( J )
                    272:                   STEMP = S( J )
                    273:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    274:                      DO 10 I = 1, N
                    275:                         TEMP = A( J+1, I )
                    276:                         A( J+1, I ) = CTEMP*TEMP - STEMP*A( J, I )
                    277:                         A( J, I ) = STEMP*TEMP + CTEMP*A( J, I )
                    278:    10                CONTINUE
                    279:                   END IF
                    280:    20          CONTINUE
                    281:             ELSE IF( LSAME( DIRECT, 'B' ) ) THEN
                    282:                DO 40 J = M - 1, 1, -1
                    283:                   CTEMP = C( J )
                    284:                   STEMP = S( J )
                    285:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    286:                      DO 30 I = 1, N
                    287:                         TEMP = A( J+1, I )
                    288:                         A( J+1, I ) = CTEMP*TEMP - STEMP*A( J, I )
                    289:                         A( J, I ) = STEMP*TEMP + CTEMP*A( J, I )
                    290:    30                CONTINUE
                    291:                   END IF
                    292:    40          CONTINUE
                    293:             END IF
                    294:          ELSE IF( LSAME( PIVOT, 'T' ) ) THEN
                    295:             IF( LSAME( DIRECT, 'F' ) ) THEN
                    296:                DO 60 J = 2, M
                    297:                   CTEMP = C( J-1 )
                    298:                   STEMP = S( J-1 )
                    299:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    300:                      DO 50 I = 1, N
                    301:                         TEMP = A( J, I )
                    302:                         A( J, I ) = CTEMP*TEMP - STEMP*A( 1, I )
                    303:                         A( 1, I ) = STEMP*TEMP + CTEMP*A( 1, I )
                    304:    50                CONTINUE
                    305:                   END IF
                    306:    60          CONTINUE
                    307:             ELSE IF( LSAME( DIRECT, 'B' ) ) THEN
                    308:                DO 80 J = M, 2, -1
                    309:                   CTEMP = C( J-1 )
                    310:                   STEMP = S( J-1 )
                    311:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    312:                      DO 70 I = 1, N
                    313:                         TEMP = A( J, I )
                    314:                         A( J, I ) = CTEMP*TEMP - STEMP*A( 1, I )
                    315:                         A( 1, I ) = STEMP*TEMP + CTEMP*A( 1, I )
                    316:    70                CONTINUE
                    317:                   END IF
                    318:    80          CONTINUE
                    319:             END IF
                    320:          ELSE IF( LSAME( PIVOT, 'B' ) ) THEN
                    321:             IF( LSAME( DIRECT, 'F' ) ) THEN
                    322:                DO 100 J = 1, M - 1
                    323:                   CTEMP = C( J )
                    324:                   STEMP = S( J )
                    325:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    326:                      DO 90 I = 1, N
                    327:                         TEMP = A( J, I )
                    328:                         A( J, I ) = STEMP*A( M, I ) + CTEMP*TEMP
                    329:                         A( M, I ) = CTEMP*A( M, I ) - STEMP*TEMP
                    330:    90                CONTINUE
                    331:                   END IF
                    332:   100          CONTINUE
                    333:             ELSE IF( LSAME( DIRECT, 'B' ) ) THEN
                    334:                DO 120 J = M - 1, 1, -1
                    335:                   CTEMP = C( J )
                    336:                   STEMP = S( J )
                    337:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    338:                      DO 110 I = 1, N
                    339:                         TEMP = A( J, I )
                    340:                         A( J, I ) = STEMP*A( M, I ) + CTEMP*TEMP
                    341:                         A( M, I ) = CTEMP*A( M, I ) - STEMP*TEMP
                    342:   110                CONTINUE
                    343:                   END IF
                    344:   120          CONTINUE
                    345:             END IF
                    346:          END IF
                    347:       ELSE IF( LSAME( SIDE, 'R' ) ) THEN
                    348: *
1.8       bertrand  349: *        Form A * P**T
1.1       bertrand  350: *
                    351:          IF( LSAME( PIVOT, 'V' ) ) THEN
                    352:             IF( LSAME( DIRECT, 'F' ) ) THEN
                    353:                DO 140 J = 1, N - 1
                    354:                   CTEMP = C( J )
                    355:                   STEMP = S( J )
                    356:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    357:                      DO 130 I = 1, M
                    358:                         TEMP = A( I, J+1 )
                    359:                         A( I, J+1 ) = CTEMP*TEMP - STEMP*A( I, J )
                    360:                         A( I, J ) = STEMP*TEMP + CTEMP*A( I, J )
                    361:   130                CONTINUE
                    362:                   END IF
                    363:   140          CONTINUE
                    364:             ELSE IF( LSAME( DIRECT, 'B' ) ) THEN
                    365:                DO 160 J = N - 1, 1, -1
                    366:                   CTEMP = C( J )
                    367:                   STEMP = S( J )
                    368:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    369:                      DO 150 I = 1, M
                    370:                         TEMP = A( I, J+1 )
                    371:                         A( I, J+1 ) = CTEMP*TEMP - STEMP*A( I, J )
                    372:                         A( I, J ) = STEMP*TEMP + CTEMP*A( I, J )
                    373:   150                CONTINUE
                    374:                   END IF
                    375:   160          CONTINUE
                    376:             END IF
                    377:          ELSE IF( LSAME( PIVOT, 'T' ) ) THEN
                    378:             IF( LSAME( DIRECT, 'F' ) ) THEN
                    379:                DO 180 J = 2, N
                    380:                   CTEMP = C( J-1 )
                    381:                   STEMP = S( J-1 )
                    382:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    383:                      DO 170 I = 1, M
                    384:                         TEMP = A( I, J )
                    385:                         A( I, J ) = CTEMP*TEMP - STEMP*A( I, 1 )
                    386:                         A( I, 1 ) = STEMP*TEMP + CTEMP*A( I, 1 )
                    387:   170                CONTINUE
                    388:                   END IF
                    389:   180          CONTINUE
                    390:             ELSE IF( LSAME( DIRECT, 'B' ) ) THEN
                    391:                DO 200 J = N, 2, -1
                    392:                   CTEMP = C( J-1 )
                    393:                   STEMP = S( J-1 )
                    394:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    395:                      DO 190 I = 1, M
                    396:                         TEMP = A( I, J )
                    397:                         A( I, J ) = CTEMP*TEMP - STEMP*A( I, 1 )
                    398:                         A( I, 1 ) = STEMP*TEMP + CTEMP*A( I, 1 )
                    399:   190                CONTINUE
                    400:                   END IF
                    401:   200          CONTINUE
                    402:             END IF
                    403:          ELSE IF( LSAME( PIVOT, 'B' ) ) THEN
                    404:             IF( LSAME( DIRECT, 'F' ) ) THEN
                    405:                DO 220 J = 1, N - 1
                    406:                   CTEMP = C( J )
                    407:                   STEMP = S( J )
                    408:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    409:                      DO 210 I = 1, M
                    410:                         TEMP = A( I, J )
                    411:                         A( I, J ) = STEMP*A( I, N ) + CTEMP*TEMP
                    412:                         A( I, N ) = CTEMP*A( I, N ) - STEMP*TEMP
                    413:   210                CONTINUE
                    414:                   END IF
                    415:   220          CONTINUE
                    416:             ELSE IF( LSAME( DIRECT, 'B' ) ) THEN
                    417:                DO 240 J = N - 1, 1, -1
                    418:                   CTEMP = C( J )
                    419:                   STEMP = S( J )
                    420:                   IF( ( CTEMP.NE.ONE ) .OR. ( STEMP.NE.ZERO ) ) THEN
                    421:                      DO 230 I = 1, M
                    422:                         TEMP = A( I, J )
                    423:                         A( I, J ) = STEMP*A( I, N ) + CTEMP*TEMP
                    424:                         A( I, N ) = CTEMP*A( I, N ) - STEMP*TEMP
                    425:   230                CONTINUE
                    426:                   END IF
                    427:   240          CONTINUE
                    428:             END IF
                    429:          END IF
                    430:       END IF
                    431: *
                    432:       RETURN
                    433: *
                    434: *     End of ZLASR
                    435: *
                    436:       END

CVSweb interface <joel.bertrand@systella.fr>