File:  [local] / rpl / lapack / lapack / zlals0.f
Revision 1.19: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:29 2023 UTC (8 months, 3 weeks ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_35, rpl-4_1_34, HEAD
Première mise à jour de lapack et blas.

    1: *> \brief \b ZLALS0 applies back multiplying factors in solving the least squares problem using divide and conquer SVD approach. Used by sgelsd.
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZLALS0 + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlals0.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlals0.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlals0.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZLALS0( ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX, LDBX,
   22: *                          PERM, GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM,
   23: *                          POLES, DIFL, DIFR, Z, K, C, S, RWORK, INFO )
   24: *
   25: *       .. Scalar Arguments ..
   26: *       INTEGER            GIVPTR, ICOMPQ, INFO, K, LDB, LDBX, LDGCOL,
   27: *      $                   LDGNUM, NL, NR, NRHS, SQRE
   28: *       DOUBLE PRECISION   C, S
   29: *       ..
   30: *       .. Array Arguments ..
   31: *       INTEGER            GIVCOL( LDGCOL, * ), PERM( * )
   32: *       DOUBLE PRECISION   DIFL( * ), DIFR( LDGNUM, * ),
   33: *      $                   GIVNUM( LDGNUM, * ), POLES( LDGNUM, * ),
   34: *      $                   RWORK( * ), Z( * )
   35: *       COMPLEX*16         B( LDB, * ), BX( LDBX, * )
   36: *       ..
   37: *
   38: *
   39: *> \par Purpose:
   40: *  =============
   41: *>
   42: *> \verbatim
   43: *>
   44: *> ZLALS0 applies back the multiplying factors of either the left or the
   45: *> right singular vector matrix of a diagonal matrix appended by a row
   46: *> to the right hand side matrix B in solving the least squares problem
   47: *> using the divide-and-conquer SVD approach.
   48: *>
   49: *> For the left singular vector matrix, three types of orthogonal
   50: *> matrices are involved:
   51: *>
   52: *> (1L) Givens rotations: the number of such rotations is GIVPTR; the
   53: *>      pairs of columns/rows they were applied to are stored in GIVCOL;
   54: *>      and the C- and S-values of these rotations are stored in GIVNUM.
   55: *>
   56: *> (2L) Permutation. The (NL+1)-st row of B is to be moved to the first
   57: *>      row, and for J=2:N, PERM(J)-th row of B is to be moved to the
   58: *>      J-th row.
   59: *>
   60: *> (3L) The left singular vector matrix of the remaining matrix.
   61: *>
   62: *> For the right singular vector matrix, four types of orthogonal
   63: *> matrices are involved:
   64: *>
   65: *> (1R) The right singular vector matrix of the remaining matrix.
   66: *>
   67: *> (2R) If SQRE = 1, one extra Givens rotation to generate the right
   68: *>      null space.
   69: *>
   70: *> (3R) The inverse transformation of (2L).
   71: *>
   72: *> (4R) The inverse transformation of (1L).
   73: *> \endverbatim
   74: *
   75: *  Arguments:
   76: *  ==========
   77: *
   78: *> \param[in] ICOMPQ
   79: *> \verbatim
   80: *>          ICOMPQ is INTEGER
   81: *>         Specifies whether singular vectors are to be computed in
   82: *>         factored form:
   83: *>         = 0: Left singular vector matrix.
   84: *>         = 1: Right singular vector matrix.
   85: *> \endverbatim
   86: *>
   87: *> \param[in] NL
   88: *> \verbatim
   89: *>          NL is INTEGER
   90: *>         The row dimension of the upper block. NL >= 1.
   91: *> \endverbatim
   92: *>
   93: *> \param[in] NR
   94: *> \verbatim
   95: *>          NR is INTEGER
   96: *>         The row dimension of the lower block. NR >= 1.
   97: *> \endverbatim
   98: *>
   99: *> \param[in] SQRE
  100: *> \verbatim
  101: *>          SQRE is INTEGER
  102: *>         = 0: the lower block is an NR-by-NR square matrix.
  103: *>         = 1: the lower block is an NR-by-(NR+1) rectangular matrix.
  104: *>
  105: *>         The bidiagonal matrix has row dimension N = NL + NR + 1,
  106: *>         and column dimension M = N + SQRE.
  107: *> \endverbatim
  108: *>
  109: *> \param[in] NRHS
  110: *> \verbatim
  111: *>          NRHS is INTEGER
  112: *>         The number of columns of B and BX. NRHS must be at least 1.
  113: *> \endverbatim
  114: *>
  115: *> \param[in,out] B
  116: *> \verbatim
  117: *>          B is COMPLEX*16 array, dimension ( LDB, NRHS )
  118: *>         On input, B contains the right hand sides of the least
  119: *>         squares problem in rows 1 through M. On output, B contains
  120: *>         the solution X in rows 1 through N.
  121: *> \endverbatim
  122: *>
  123: *> \param[in] LDB
  124: *> \verbatim
  125: *>          LDB is INTEGER
  126: *>         The leading dimension of B. LDB must be at least
  127: *>         max(1,MAX( M, N ) ).
  128: *> \endverbatim
  129: *>
  130: *> \param[out] BX
  131: *> \verbatim
  132: *>          BX is COMPLEX*16 array, dimension ( LDBX, NRHS )
  133: *> \endverbatim
  134: *>
  135: *> \param[in] LDBX
  136: *> \verbatim
  137: *>          LDBX is INTEGER
  138: *>         The leading dimension of BX.
  139: *> \endverbatim
  140: *>
  141: *> \param[in] PERM
  142: *> \verbatim
  143: *>          PERM is INTEGER array, dimension ( N )
  144: *>         The permutations (from deflation and sorting) applied
  145: *>         to the two blocks.
  146: *> \endverbatim
  147: *>
  148: *> \param[in] GIVPTR
  149: *> \verbatim
  150: *>          GIVPTR is INTEGER
  151: *>         The number of Givens rotations which took place in this
  152: *>         subproblem.
  153: *> \endverbatim
  154: *>
  155: *> \param[in] GIVCOL
  156: *> \verbatim
  157: *>          GIVCOL is INTEGER array, dimension ( LDGCOL, 2 )
  158: *>         Each pair of numbers indicates a pair of rows/columns
  159: *>         involved in a Givens rotation.
  160: *> \endverbatim
  161: *>
  162: *> \param[in] LDGCOL
  163: *> \verbatim
  164: *>          LDGCOL is INTEGER
  165: *>         The leading dimension of GIVCOL, must be at least N.
  166: *> \endverbatim
  167: *>
  168: *> \param[in] GIVNUM
  169: *> \verbatim
  170: *>          GIVNUM is DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
  171: *>         Each number indicates the C or S value used in the
  172: *>         corresponding Givens rotation.
  173: *> \endverbatim
  174: *>
  175: *> \param[in] LDGNUM
  176: *> \verbatim
  177: *>          LDGNUM is INTEGER
  178: *>         The leading dimension of arrays DIFR, POLES and
  179: *>         GIVNUM, must be at least K.
  180: *> \endverbatim
  181: *>
  182: *> \param[in] POLES
  183: *> \verbatim
  184: *>          POLES is DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
  185: *>         On entry, POLES(1:K, 1) contains the new singular
  186: *>         values obtained from solving the secular equation, and
  187: *>         POLES(1:K, 2) is an array containing the poles in the secular
  188: *>         equation.
  189: *> \endverbatim
  190: *>
  191: *> \param[in] DIFL
  192: *> \verbatim
  193: *>          DIFL is DOUBLE PRECISION array, dimension ( K ).
  194: *>         On entry, DIFL(I) is the distance between I-th updated
  195: *>         (undeflated) singular value and the I-th (undeflated) old
  196: *>         singular value.
  197: *> \endverbatim
  198: *>
  199: *> \param[in] DIFR
  200: *> \verbatim
  201: *>          DIFR is DOUBLE PRECISION array, dimension ( LDGNUM, 2 ).
  202: *>         On entry, DIFR(I, 1) contains the distances between I-th
  203: *>         updated (undeflated) singular value and the I+1-th
  204: *>         (undeflated) old singular value. And DIFR(I, 2) is the
  205: *>         normalizing factor for the I-th right singular vector.
  206: *> \endverbatim
  207: *>
  208: *> \param[in] Z
  209: *> \verbatim
  210: *>          Z is DOUBLE PRECISION array, dimension ( K )
  211: *>         Contain the components of the deflation-adjusted updating row
  212: *>         vector.
  213: *> \endverbatim
  214: *>
  215: *> \param[in] K
  216: *> \verbatim
  217: *>          K is INTEGER
  218: *>         Contains the dimension of the non-deflated matrix,
  219: *>         This is the order of the related secular equation. 1 <= K <=N.
  220: *> \endverbatim
  221: *>
  222: *> \param[in] C
  223: *> \verbatim
  224: *>          C is DOUBLE PRECISION
  225: *>         C contains garbage if SQRE =0 and the C-value of a Givens
  226: *>         rotation related to the right null space if SQRE = 1.
  227: *> \endverbatim
  228: *>
  229: *> \param[in] S
  230: *> \verbatim
  231: *>          S is DOUBLE PRECISION
  232: *>         S contains garbage if SQRE =0 and the S-value of a Givens
  233: *>         rotation related to the right null space if SQRE = 1.
  234: *> \endverbatim
  235: *>
  236: *> \param[out] RWORK
  237: *> \verbatim
  238: *>          RWORK is DOUBLE PRECISION array, dimension
  239: *>         ( K*(1+NRHS) + 2*NRHS )
  240: *> \endverbatim
  241: *>
  242: *> \param[out] INFO
  243: *> \verbatim
  244: *>          INFO is INTEGER
  245: *>          = 0:  successful exit.
  246: *>          < 0:  if INFO = -i, the i-th argument had an illegal value.
  247: *> \endverbatim
  248: *
  249: *  Authors:
  250: *  ========
  251: *
  252: *> \author Univ. of Tennessee
  253: *> \author Univ. of California Berkeley
  254: *> \author Univ. of Colorado Denver
  255: *> \author NAG Ltd.
  256: *
  257: *> \ingroup complex16OTHERcomputational
  258: *
  259: *> \par Contributors:
  260: *  ==================
  261: *>
  262: *>     Ming Gu and Ren-Cang Li, Computer Science Division, University of
  263: *>       California at Berkeley, USA \n
  264: *>     Osni Marques, LBNL/NERSC, USA \n
  265: *
  266: *  =====================================================================
  267:       SUBROUTINE ZLALS0( ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX, LDBX,
  268:      $                   PERM, GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM,
  269:      $                   POLES, DIFL, DIFR, Z, K, C, S, RWORK, INFO )
  270: *
  271: *  -- LAPACK computational routine --
  272: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  273: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  274: *
  275: *     .. Scalar Arguments ..
  276:       INTEGER            GIVPTR, ICOMPQ, INFO, K, LDB, LDBX, LDGCOL,
  277:      $                   LDGNUM, NL, NR, NRHS, SQRE
  278:       DOUBLE PRECISION   C, S
  279: *     ..
  280: *     .. Array Arguments ..
  281:       INTEGER            GIVCOL( LDGCOL, * ), PERM( * )
  282:       DOUBLE PRECISION   DIFL( * ), DIFR( LDGNUM, * ),
  283:      $                   GIVNUM( LDGNUM, * ), POLES( LDGNUM, * ),
  284:      $                   RWORK( * ), Z( * )
  285:       COMPLEX*16         B( LDB, * ), BX( LDBX, * )
  286: *     ..
  287: *
  288: *  =====================================================================
  289: *
  290: *     .. Parameters ..
  291:       DOUBLE PRECISION   ONE, ZERO, NEGONE
  292:       PARAMETER          ( ONE = 1.0D0, ZERO = 0.0D0, NEGONE = -1.0D0 )
  293: *     ..
  294: *     .. Local Scalars ..
  295:       INTEGER            I, J, JCOL, JROW, M, N, NLP1
  296:       DOUBLE PRECISION   DIFLJ, DIFRJ, DJ, DSIGJ, DSIGJP, TEMP
  297: *     ..
  298: *     .. External Subroutines ..
  299:       EXTERNAL           DGEMV, XERBLA, ZCOPY, ZDROT, ZDSCAL, ZLACPY,
  300:      $                   ZLASCL
  301: *     ..
  302: *     .. External Functions ..
  303:       DOUBLE PRECISION   DLAMC3, DNRM2
  304:       EXTERNAL           DLAMC3, DNRM2
  305: *     ..
  306: *     .. Intrinsic Functions ..
  307:       INTRINSIC          DBLE, DCMPLX, DIMAG, MAX
  308: *     ..
  309: *     .. Executable Statements ..
  310: *
  311: *     Test the input parameters.
  312: *
  313:       INFO = 0
  314:       N = NL + NR + 1
  315: *
  316:       IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
  317:          INFO = -1
  318:       ELSE IF( NL.LT.1 ) THEN
  319:          INFO = -2
  320:       ELSE IF( NR.LT.1 ) THEN
  321:          INFO = -3
  322:       ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN
  323:          INFO = -4
  324:       ELSE IF( NRHS.LT.1 ) THEN
  325:          INFO = -5
  326:       ELSE IF( LDB.LT.N ) THEN
  327:          INFO = -7
  328:       ELSE IF( LDBX.LT.N ) THEN
  329:          INFO = -9
  330:       ELSE IF( GIVPTR.LT.0 ) THEN
  331:          INFO = -11
  332:       ELSE IF( LDGCOL.LT.N ) THEN
  333:          INFO = -13
  334:       ELSE IF( LDGNUM.LT.N ) THEN
  335:          INFO = -15
  336:       ELSE IF( K.LT.1 ) THEN
  337:          INFO = -20
  338:       END IF
  339:       IF( INFO.NE.0 ) THEN
  340:          CALL XERBLA( 'ZLALS0', -INFO )
  341:          RETURN
  342:       END IF
  343: *
  344:       M = N + SQRE
  345:       NLP1 = NL + 1
  346: *
  347:       IF( ICOMPQ.EQ.0 ) THEN
  348: *
  349: *        Apply back orthogonal transformations from the left.
  350: *
  351: *        Step (1L): apply back the Givens rotations performed.
  352: *
  353:          DO 10 I = 1, GIVPTR
  354:             CALL ZDROT( NRHS, B( GIVCOL( I, 2 ), 1 ), LDB,
  355:      $                  B( GIVCOL( I, 1 ), 1 ), LDB, GIVNUM( I, 2 ),
  356:      $                  GIVNUM( I, 1 ) )
  357:    10    CONTINUE
  358: *
  359: *        Step (2L): permute rows of B.
  360: *
  361:          CALL ZCOPY( NRHS, B( NLP1, 1 ), LDB, BX( 1, 1 ), LDBX )
  362:          DO 20 I = 2, N
  363:             CALL ZCOPY( NRHS, B( PERM( I ), 1 ), LDB, BX( I, 1 ), LDBX )
  364:    20    CONTINUE
  365: *
  366: *        Step (3L): apply the inverse of the left singular vector
  367: *        matrix to BX.
  368: *
  369:          IF( K.EQ.1 ) THEN
  370:             CALL ZCOPY( NRHS, BX, LDBX, B, LDB )
  371:             IF( Z( 1 ).LT.ZERO ) THEN
  372:                CALL ZDSCAL( NRHS, NEGONE, B, LDB )
  373:             END IF
  374:          ELSE
  375:             DO 100 J = 1, K
  376:                DIFLJ = DIFL( J )
  377:                DJ = POLES( J, 1 )
  378:                DSIGJ = -POLES( J, 2 )
  379:                IF( J.LT.K ) THEN
  380:                   DIFRJ = -DIFR( J, 1 )
  381:                   DSIGJP = -POLES( J+1, 2 )
  382:                END IF
  383:                IF( ( Z( J ).EQ.ZERO ) .OR. ( POLES( J, 2 ).EQ.ZERO ) )
  384:      $              THEN
  385:                   RWORK( J ) = ZERO
  386:                ELSE
  387:                   RWORK( J ) = -POLES( J, 2 )*Z( J ) / DIFLJ /
  388:      $                         ( POLES( J, 2 )+DJ )
  389:                END IF
  390:                DO 30 I = 1, J - 1
  391:                   IF( ( Z( I ).EQ.ZERO ) .OR.
  392:      $                ( POLES( I, 2 ).EQ.ZERO ) ) THEN
  393:                      RWORK( I ) = ZERO
  394:                   ELSE
  395:                      RWORK( I ) = POLES( I, 2 )*Z( I ) /
  396:      $                            ( DLAMC3( POLES( I, 2 ), DSIGJ )-
  397:      $                            DIFLJ ) / ( POLES( I, 2 )+DJ )
  398:                   END IF
  399:    30          CONTINUE
  400:                DO 40 I = J + 1, K
  401:                   IF( ( Z( I ).EQ.ZERO ) .OR.
  402:      $                ( POLES( I, 2 ).EQ.ZERO ) ) THEN
  403:                      RWORK( I ) = ZERO
  404:                   ELSE
  405:                      RWORK( I ) = POLES( I, 2 )*Z( I ) /
  406:      $                            ( DLAMC3( POLES( I, 2 ), DSIGJP )+
  407:      $                            DIFRJ ) / ( POLES( I, 2 )+DJ )
  408:                   END IF
  409:    40          CONTINUE
  410:                RWORK( 1 ) = NEGONE
  411:                TEMP = DNRM2( K, RWORK, 1 )
  412: *
  413: *              Since B and BX are complex, the following call to DGEMV
  414: *              is performed in two steps (real and imaginary parts).
  415: *
  416: *              CALL DGEMV( 'T', K, NRHS, ONE, BX, LDBX, WORK, 1, ZERO,
  417: *    $                     B( J, 1 ), LDB )
  418: *
  419:                I = K + NRHS*2
  420:                DO 60 JCOL = 1, NRHS
  421:                   DO 50 JROW = 1, K
  422:                      I = I + 1
  423:                      RWORK( I ) = DBLE( BX( JROW, JCOL ) )
  424:    50             CONTINUE
  425:    60          CONTINUE
  426:                CALL DGEMV( 'T', K, NRHS, ONE, RWORK( 1+K+NRHS*2 ), K,
  427:      $                     RWORK( 1 ), 1, ZERO, RWORK( 1+K ), 1 )
  428:                I = K + NRHS*2
  429:                DO 80 JCOL = 1, NRHS
  430:                   DO 70 JROW = 1, K
  431:                      I = I + 1
  432:                      RWORK( I ) = DIMAG( BX( JROW, JCOL ) )
  433:    70             CONTINUE
  434:    80          CONTINUE
  435:                CALL DGEMV( 'T', K, NRHS, ONE, RWORK( 1+K+NRHS*2 ), K,
  436:      $                     RWORK( 1 ), 1, ZERO, RWORK( 1+K+NRHS ), 1 )
  437:                DO 90 JCOL = 1, NRHS
  438:                   B( J, JCOL ) = DCMPLX( RWORK( JCOL+K ),
  439:      $                           RWORK( JCOL+K+NRHS ) )
  440:    90          CONTINUE
  441:                CALL ZLASCL( 'G', 0, 0, TEMP, ONE, 1, NRHS, B( J, 1 ),
  442:      $                      LDB, INFO )
  443:   100       CONTINUE
  444:          END IF
  445: *
  446: *        Move the deflated rows of BX to B also.
  447: *
  448:          IF( K.LT.MAX( M, N ) )
  449:      $      CALL ZLACPY( 'A', N-K, NRHS, BX( K+1, 1 ), LDBX,
  450:      $                   B( K+1, 1 ), LDB )
  451:       ELSE
  452: *
  453: *        Apply back the right orthogonal transformations.
  454: *
  455: *        Step (1R): apply back the new right singular vector matrix
  456: *        to B.
  457: *
  458:          IF( K.EQ.1 ) THEN
  459:             CALL ZCOPY( NRHS, B, LDB, BX, LDBX )
  460:          ELSE
  461:             DO 180 J = 1, K
  462:                DSIGJ = POLES( J, 2 )
  463:                IF( Z( J ).EQ.ZERO ) THEN
  464:                   RWORK( J ) = ZERO
  465:                ELSE
  466:                   RWORK( J ) = -Z( J ) / DIFL( J ) /
  467:      $                         ( DSIGJ+POLES( J, 1 ) ) / DIFR( J, 2 )
  468:                END IF
  469:                DO 110 I = 1, J - 1
  470:                   IF( Z( J ).EQ.ZERO ) THEN
  471:                      RWORK( I ) = ZERO
  472:                   ELSE
  473:                      RWORK( I ) = Z( J ) / ( DLAMC3( DSIGJ, -POLES( I+1,
  474:      $                            2 ) )-DIFR( I, 1 ) ) /
  475:      $                            ( DSIGJ+POLES( I, 1 ) ) / DIFR( I, 2 )
  476:                   END IF
  477:   110          CONTINUE
  478:                DO 120 I = J + 1, K
  479:                   IF( Z( J ).EQ.ZERO ) THEN
  480:                      RWORK( I ) = ZERO
  481:                   ELSE
  482:                      RWORK( I ) = Z( J ) / ( DLAMC3( DSIGJ, -POLES( I,
  483:      $                            2 ) )-DIFL( I ) ) /
  484:      $                            ( DSIGJ+POLES( I, 1 ) ) / DIFR( I, 2 )
  485:                   END IF
  486:   120          CONTINUE
  487: *
  488: *              Since B and BX are complex, the following call to DGEMV
  489: *              is performed in two steps (real and imaginary parts).
  490: *
  491: *              CALL DGEMV( 'T', K, NRHS, ONE, B, LDB, WORK, 1, ZERO,
  492: *    $                     BX( J, 1 ), LDBX )
  493: *
  494:                I = K + NRHS*2
  495:                DO 140 JCOL = 1, NRHS
  496:                   DO 130 JROW = 1, K
  497:                      I = I + 1
  498:                      RWORK( I ) = DBLE( B( JROW, JCOL ) )
  499:   130             CONTINUE
  500:   140          CONTINUE
  501:                CALL DGEMV( 'T', K, NRHS, ONE, RWORK( 1+K+NRHS*2 ), K,
  502:      $                     RWORK( 1 ), 1, ZERO, RWORK( 1+K ), 1 )
  503:                I = K + NRHS*2
  504:                DO 160 JCOL = 1, NRHS
  505:                   DO 150 JROW = 1, K
  506:                      I = I + 1
  507:                      RWORK( I ) = DIMAG( B( JROW, JCOL ) )
  508:   150             CONTINUE
  509:   160          CONTINUE
  510:                CALL DGEMV( 'T', K, NRHS, ONE, RWORK( 1+K+NRHS*2 ), K,
  511:      $                     RWORK( 1 ), 1, ZERO, RWORK( 1+K+NRHS ), 1 )
  512:                DO 170 JCOL = 1, NRHS
  513:                   BX( J, JCOL ) = DCMPLX( RWORK( JCOL+K ),
  514:      $                            RWORK( JCOL+K+NRHS ) )
  515:   170          CONTINUE
  516:   180       CONTINUE
  517:          END IF
  518: *
  519: *        Step (2R): if SQRE = 1, apply back the rotation that is
  520: *        related to the right null space of the subproblem.
  521: *
  522:          IF( SQRE.EQ.1 ) THEN
  523:             CALL ZCOPY( NRHS, B( M, 1 ), LDB, BX( M, 1 ), LDBX )
  524:             CALL ZDROT( NRHS, BX( 1, 1 ), LDBX, BX( M, 1 ), LDBX, C, S )
  525:          END IF
  526:          IF( K.LT.MAX( M, N ) )
  527:      $      CALL ZLACPY( 'A', N-K, NRHS, B( K+1, 1 ), LDB, BX( K+1, 1 ),
  528:      $                   LDBX )
  529: *
  530: *        Step (3R): permute rows of B.
  531: *
  532:          CALL ZCOPY( NRHS, BX( 1, 1 ), LDBX, B( NLP1, 1 ), LDB )
  533:          IF( SQRE.EQ.1 ) THEN
  534:             CALL ZCOPY( NRHS, BX( M, 1 ), LDBX, B( M, 1 ), LDB )
  535:          END IF
  536:          DO 190 I = 2, N
  537:             CALL ZCOPY( NRHS, BX( I, 1 ), LDBX, B( PERM( I ), 1 ), LDB )
  538:   190    CONTINUE
  539: *
  540: *        Step (4R): apply back the Givens rotations performed.
  541: *
  542:          DO 200 I = GIVPTR, 1, -1
  543:             CALL ZDROT( NRHS, B( GIVCOL( I, 2 ), 1 ), LDB,
  544:      $                  B( GIVCOL( I, 1 ), 1 ), LDB, GIVNUM( I, 2 ),
  545:      $                  -GIVNUM( I, 1 ) )
  546:   200    CONTINUE
  547:       END IF
  548: *
  549:       RETURN
  550: *
  551: *     End of ZLALS0
  552: *
  553:       END

CVSweb interface <joel.bertrand@systella.fr>