File:  [local] / rpl / lapack / lapack / dorm2r.f
Revision 1.19: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:02 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 DORM2R multiplies a general matrix by the orthogonal matrix from a QR factorization determined by sgeqrf (unblocked algorithm).
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download DORM2R + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dorm2r.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dorm2r.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorm2r.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE DORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
   22: *                          WORK, INFO )
   23: *
   24: *       .. Scalar Arguments ..
   25: *       CHARACTER          SIDE, TRANS
   26: *       INTEGER            INFO, K, LDA, LDC, M, N
   27: *       ..
   28: *       .. Array Arguments ..
   29: *       DOUBLE PRECISION   A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
   30: *       ..
   31: *
   32: *
   33: *> \par Purpose:
   34: *  =============
   35: *>
   36: *> \verbatim
   37: *>
   38: *> DORM2R overwrites the general real m by n matrix C with
   39: *>
   40: *>       Q * C  if SIDE = 'L' and TRANS = 'N', or
   41: *>
   42: *>       Q**T* C  if SIDE = 'L' and TRANS = 'T', or
   43: *>
   44: *>       C * Q  if SIDE = 'R' and TRANS = 'N', or
   45: *>
   46: *>       C * Q**T if SIDE = 'R' and TRANS = 'T',
   47: *>
   48: *> where Q is a real orthogonal matrix defined as the product of k
   49: *> elementary reflectors
   50: *>
   51: *>       Q = H(1) H(2) . . . H(k)
   52: *>
   53: *> as returned by DGEQRF. Q is of order m if SIDE = 'L' and of order n
   54: *> if SIDE = 'R'.
   55: *> \endverbatim
   56: *
   57: *  Arguments:
   58: *  ==========
   59: *
   60: *> \param[in] SIDE
   61: *> \verbatim
   62: *>          SIDE is CHARACTER*1
   63: *>          = 'L': apply Q or Q**T from the Left
   64: *>          = 'R': apply Q or Q**T from the Right
   65: *> \endverbatim
   66: *>
   67: *> \param[in] TRANS
   68: *> \verbatim
   69: *>          TRANS is CHARACTER*1
   70: *>          = 'N': apply Q  (No transpose)
   71: *>          = 'T': apply Q**T (Transpose)
   72: *> \endverbatim
   73: *>
   74: *> \param[in] M
   75: *> \verbatim
   76: *>          M is INTEGER
   77: *>          The number of rows of the matrix C. M >= 0.
   78: *> \endverbatim
   79: *>
   80: *> \param[in] N
   81: *> \verbatim
   82: *>          N is INTEGER
   83: *>          The number of columns of the matrix C. N >= 0.
   84: *> \endverbatim
   85: *>
   86: *> \param[in] K
   87: *> \verbatim
   88: *>          K is INTEGER
   89: *>          The number of elementary reflectors whose product defines
   90: *>          the matrix Q.
   91: *>          If SIDE = 'L', M >= K >= 0;
   92: *>          if SIDE = 'R', N >= K >= 0.
   93: *> \endverbatim
   94: *>
   95: *> \param[in] A
   96: *> \verbatim
   97: *>          A is DOUBLE PRECISION array, dimension (LDA,K)
   98: *>          The i-th column must contain the vector which defines the
   99: *>          elementary reflector H(i), for i = 1,2,...,k, as returned by
  100: *>          DGEQRF in the first k columns of its array argument A.
  101: *>          A is modified by the routine but restored on exit.
  102: *> \endverbatim
  103: *>
  104: *> \param[in] LDA
  105: *> \verbatim
  106: *>          LDA is INTEGER
  107: *>          The leading dimension of the array A.
  108: *>          If SIDE = 'L', LDA >= max(1,M);
  109: *>          if SIDE = 'R', LDA >= max(1,N).
  110: *> \endverbatim
  111: *>
  112: *> \param[in] TAU
  113: *> \verbatim
  114: *>          TAU is DOUBLE PRECISION array, dimension (K)
  115: *>          TAU(i) must contain the scalar factor of the elementary
  116: *>          reflector H(i), as returned by DGEQRF.
  117: *> \endverbatim
  118: *>
  119: *> \param[in,out] C
  120: *> \verbatim
  121: *>          C is DOUBLE PRECISION array, dimension (LDC,N)
  122: *>          On entry, the m by n matrix C.
  123: *>          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
  124: *> \endverbatim
  125: *>
  126: *> \param[in] LDC
  127: *> \verbatim
  128: *>          LDC is INTEGER
  129: *>          The leading dimension of the array C. LDC >= max(1,M).
  130: *> \endverbatim
  131: *>
  132: *> \param[out] WORK
  133: *> \verbatim
  134: *>          WORK is DOUBLE PRECISION array, dimension
  135: *>                                   (N) if SIDE = 'L',
  136: *>                                   (M) if SIDE = 'R'
  137: *> \endverbatim
  138: *>
  139: *> \param[out] INFO
  140: *> \verbatim
  141: *>          INFO is INTEGER
  142: *>          = 0: successful exit
  143: *>          < 0: if INFO = -i, the i-th argument had an illegal value
  144: *> \endverbatim
  145: *
  146: *  Authors:
  147: *  ========
  148: *
  149: *> \author Univ. of Tennessee
  150: *> \author Univ. of California Berkeley
  151: *> \author Univ. of Colorado Denver
  152: *> \author NAG Ltd.
  153: *
  154: *> \ingroup doubleOTHERcomputational
  155: *
  156: *  =====================================================================
  157:       SUBROUTINE DORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
  158:      $                   WORK, INFO )
  159: *
  160: *  -- LAPACK computational routine --
  161: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  162: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  163: *
  164: *     .. Scalar Arguments ..
  165:       CHARACTER          SIDE, TRANS
  166:       INTEGER            INFO, K, LDA, LDC, M, N
  167: *     ..
  168: *     .. Array Arguments ..
  169:       DOUBLE PRECISION   A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
  170: *     ..
  171: *
  172: *  =====================================================================
  173: *
  174: *     .. Parameters ..
  175:       DOUBLE PRECISION   ONE
  176:       PARAMETER          ( ONE = 1.0D+0 )
  177: *     ..
  178: *     .. Local Scalars ..
  179:       LOGICAL            LEFT, NOTRAN
  180:       INTEGER            I, I1, I2, I3, IC, JC, MI, NI, NQ
  181:       DOUBLE PRECISION   AII
  182: *     ..
  183: *     .. External Functions ..
  184:       LOGICAL            LSAME
  185:       EXTERNAL           LSAME
  186: *     ..
  187: *     .. External Subroutines ..
  188:       EXTERNAL           DLARF, XERBLA
  189: *     ..
  190: *     .. Intrinsic Functions ..
  191:       INTRINSIC          MAX
  192: *     ..
  193: *     .. Executable Statements ..
  194: *
  195: *     Test the input arguments
  196: *
  197:       INFO = 0
  198:       LEFT = LSAME( SIDE, 'L' )
  199:       NOTRAN = LSAME( TRANS, 'N' )
  200: *
  201: *     NQ is the order of Q
  202: *
  203:       IF( LEFT ) THEN
  204:          NQ = M
  205:       ELSE
  206:          NQ = N
  207:       END IF
  208:       IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
  209:          INFO = -1
  210:       ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) ) THEN
  211:          INFO = -2
  212:       ELSE IF( M.LT.0 ) THEN
  213:          INFO = -3
  214:       ELSE IF( N.LT.0 ) THEN
  215:          INFO = -4
  216:       ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN
  217:          INFO = -5
  218:       ELSE IF( LDA.LT.MAX( 1, NQ ) ) THEN
  219:          INFO = -7
  220:       ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
  221:          INFO = -10
  222:       END IF
  223:       IF( INFO.NE.0 ) THEN
  224:          CALL XERBLA( 'DORM2R', -INFO )
  225:          RETURN
  226:       END IF
  227: *
  228: *     Quick return if possible
  229: *
  230:       IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 )
  231:      $   RETURN
  232: *
  233:       IF( ( LEFT .AND. .NOT.NOTRAN ) .OR. ( .NOT.LEFT .AND. NOTRAN ) )
  234:      $     THEN
  235:          I1 = 1
  236:          I2 = K
  237:          I3 = 1
  238:       ELSE
  239:          I1 = K
  240:          I2 = 1
  241:          I3 = -1
  242:       END IF
  243: *
  244:       IF( LEFT ) THEN
  245:          NI = N
  246:          JC = 1
  247:       ELSE
  248:          MI = M
  249:          IC = 1
  250:       END IF
  251: *
  252:       DO 10 I = I1, I2, I3
  253:          IF( LEFT ) THEN
  254: *
  255: *           H(i) is applied to C(i:m,1:n)
  256: *
  257:             MI = M - I + 1
  258:             IC = I
  259:          ELSE
  260: *
  261: *           H(i) is applied to C(1:m,i:n)
  262: *
  263:             NI = N - I + 1
  264:             JC = I
  265:          END IF
  266: *
  267: *        Apply H(i)
  268: *
  269:          AII = A( I, I )
  270:          A( I, I ) = ONE
  271:          CALL DLARF( SIDE, MI, NI, A( I, I ), 1, TAU( I ), C( IC, JC ),
  272:      $               LDC, WORK )
  273:          A( I, I ) = AII
  274:    10 CONTINUE
  275:       RETURN
  276: *
  277: *     End of DORM2R
  278: *
  279:       END

CVSweb interface <joel.bertrand@systella.fr>