LAPACK 3.3.0

sormr3.f

Go to the documentation of this file.
00001       SUBROUTINE SORMR3( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
00002      $                   WORK, INFO )
00003 *
00004 *  -- LAPACK routine (version 3.2) --
00005 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00006 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00007 *     November 2006
00008 *
00009 *     .. Scalar Arguments ..
00010       CHARACTER          SIDE, TRANS
00011       INTEGER            INFO, K, L, LDA, LDC, M, N
00012 *     ..
00013 *     .. Array Arguments ..
00014       REAL               A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
00015 *     ..
00016 *
00017 *  Purpose
00018 *  =======
00019 *
00020 *  SORMR3 overwrites the general real m by n matrix C with
00021 *
00022 *        Q * C  if SIDE = 'L' and TRANS = 'N', or
00023 *
00024 *        Q'* C  if SIDE = 'L' and TRANS = 'T', or
00025 *
00026 *        C * Q  if SIDE = 'R' and TRANS = 'N', or
00027 *
00028 *        C * Q' if SIDE = 'R' and TRANS = 'T',
00029 *
00030 *  where Q is a real orthogonal matrix defined as the product of k
00031 *  elementary reflectors
00032 *
00033 *        Q = H(1) H(2) . . . H(k)
00034 *
00035 *  as returned by STZRZF. Q is of order m if SIDE = 'L' and of order n
00036 *  if SIDE = 'R'.
00037 *
00038 *  Arguments
00039 *  =========
00040 *
00041 *  SIDE    (input) CHARACTER*1
00042 *          = 'L': apply Q or Q' from the Left
00043 *          = 'R': apply Q or Q' from the Right
00044 *
00045 *  TRANS   (input) CHARACTER*1
00046 *          = 'N': apply Q  (No transpose)
00047 *          = 'T': apply Q' (Transpose)
00048 *
00049 *  M       (input) INTEGER
00050 *          The number of rows of the matrix C. M >= 0.
00051 *
00052 *  N       (input) INTEGER
00053 *          The number of columns of the matrix C. N >= 0.
00054 *
00055 *  K       (input) INTEGER
00056 *          The number of elementary reflectors whose product defines
00057 *          the matrix Q.
00058 *          If SIDE = 'L', M >= K >= 0;
00059 *          if SIDE = 'R', N >= K >= 0.
00060 *
00061 *  L       (input) INTEGER
00062 *          The number of columns of the matrix A containing
00063 *          the meaningful part of the Householder reflectors.
00064 *          If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
00065 *
00066 *  A       (input) REAL array, dimension
00067 *                               (LDA,M) if SIDE = 'L',
00068 *                               (LDA,N) if SIDE = 'R'
00069 *          The i-th row must contain the vector which defines the
00070 *          elementary reflector H(i), for i = 1,2,...,k, as returned by
00071 *          STZRZF in the last k rows of its array argument A.
00072 *          A is modified by the routine but restored on exit.
00073 *
00074 *  LDA     (input) INTEGER
00075 *          The leading dimension of the array A. LDA >= max(1,K).
00076 *
00077 *  TAU     (input) REAL array, dimension (K)
00078 *          TAU(i) must contain the scalar factor of the elementary
00079 *          reflector H(i), as returned by STZRZF.
00080 *
00081 *  C       (input/output) REAL array, dimension (LDC,N)
00082 *          On entry, the m-by-n matrix C.
00083 *          On exit, C is overwritten by Q*C or Q'*C or C*Q' or C*Q.
00084 *
00085 *  LDC     (input) INTEGER
00086 *          The leading dimension of the array C. LDC >= max(1,M).
00087 *
00088 *  WORK    (workspace) REAL array, dimension
00089 *                                   (N) if SIDE = 'L',
00090 *                                   (M) if SIDE = 'R'
00091 *
00092 *  INFO    (output) INTEGER
00093 *          = 0: successful exit
00094 *          < 0: if INFO = -i, the i-th argument had an illegal value
00095 *
00096 *  Further Details
00097 *  ===============
00098 *
00099 *  Based on contributions by
00100 *    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
00101 *
00102 *  =====================================================================
00103 *
00104 *     .. Local Scalars ..
00105       LOGICAL            LEFT, NOTRAN
00106       INTEGER            I, I1, I2, I3, IC, JA, JC, MI, NI, NQ
00107 *     ..
00108 *     .. External Functions ..
00109       LOGICAL            LSAME
00110       EXTERNAL           LSAME
00111 *     ..
00112 *     .. External Subroutines ..
00113       EXTERNAL           SLARZ, XERBLA
00114 *     ..
00115 *     .. Intrinsic Functions ..
00116       INTRINSIC          MAX
00117 *     ..
00118 *     .. Executable Statements ..
00119 *
00120 *     Test the input arguments
00121 *
00122       INFO = 0
00123       LEFT = LSAME( SIDE, 'L' )
00124       NOTRAN = LSAME( TRANS, 'N' )
00125 *
00126 *     NQ is the order of Q
00127 *
00128       IF( LEFT ) THEN
00129          NQ = M
00130       ELSE
00131          NQ = N
00132       END IF
00133       IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
00134          INFO = -1
00135       ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) ) THEN
00136          INFO = -2
00137       ELSE IF( M.LT.0 ) THEN
00138          INFO = -3
00139       ELSE IF( N.LT.0 ) THEN
00140          INFO = -4
00141       ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN
00142          INFO = -5
00143       ELSE IF( L.LT.0 .OR. ( LEFT .AND. ( L.GT.M ) ) .OR.
00144      $         ( .NOT.LEFT .AND. ( L.GT.N ) ) ) THEN
00145          INFO = -6
00146       ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
00147          INFO = -8
00148       ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
00149          INFO = -11
00150       END IF
00151       IF( INFO.NE.0 ) THEN
00152          CALL XERBLA( 'SORMR3', -INFO )
00153          RETURN
00154       END IF
00155 *
00156 *     Quick return if possible
00157 *
00158       IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 )
00159      $   RETURN
00160 *
00161       IF( ( LEFT .AND. .NOT.NOTRAN .OR. .NOT.LEFT .AND. NOTRAN ) ) THEN
00162          I1 = 1
00163          I2 = K
00164          I3 = 1
00165       ELSE
00166          I1 = K
00167          I2 = 1
00168          I3 = -1
00169       END IF
00170 *
00171       IF( LEFT ) THEN
00172          NI = N
00173          JA = M - L + 1
00174          JC = 1
00175       ELSE
00176          MI = M
00177          JA = N - L + 1
00178          IC = 1
00179       END IF
00180 *
00181       DO 10 I = I1, I2, I3
00182          IF( LEFT ) THEN
00183 *
00184 *           H(i) or H(i)' is applied to C(i:m,1:n)
00185 *
00186             MI = M - I + 1
00187             IC = I
00188          ELSE
00189 *
00190 *           H(i) or H(i)' is applied to C(1:m,i:n)
00191 *
00192             NI = N - I + 1
00193             JC = I
00194          END IF
00195 *
00196 *        Apply H(i) or H(i)'
00197 *
00198          CALL SLARZ( SIDE, MI, NI, L, A( I, JA ), LDA, TAU( I ),
00199      $               C( IC, JC ), LDC, WORK )
00200 *
00201    10 CONTINUE
00202 *
00203       RETURN
00204 *
00205 *     End of SORMR3
00206 *
00207       END
 All Files Functions