Statistiques
| Révision :

root / src / lapack / double / dormr3.f @ 2

Historique | Voir | Annoter | Télécharger (5,55 ko)

1
      SUBROUTINE DORMR3( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
2
     $                   WORK, INFO )
3
*
4
*  -- LAPACK routine (version 3.2) --
5
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
6
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7
*     November 2006
8
*
9
*     .. Scalar Arguments ..
10
      CHARACTER          SIDE, TRANS
11
      INTEGER            INFO, K, L, LDA, LDC, M, N
12
*     ..
13
*     .. Array Arguments ..
14
      DOUBLE PRECISION   A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
15
*     ..
16
*
17
*  Purpose
18
*  =======
19
*
20
*  DORMR3 overwrites the general real m by n matrix C with
21
*
22
*        Q * C  if SIDE = 'L' and TRANS = 'N', or
23
*
24
*        Q'* C  if SIDE = 'L' and TRANS = 'T', or
25
*
26
*        C * Q  if SIDE = 'R' and TRANS = 'N', or
27
*
28
*        C * Q' if SIDE = 'R' and TRANS = 'T',
29
*
30
*  where Q is a real orthogonal matrix defined as the product of k
31
*  elementary reflectors
32
*
33
*        Q = H(1) H(2) . . . H(k)
34
*
35
*  as returned by DTZRZF. Q is of order m if SIDE = 'L' and of order n
36
*  if SIDE = 'R'.
37
*
38
*  Arguments
39
*  =========
40
*
41
*  SIDE    (input) CHARACTER*1
42
*          = 'L': apply Q or Q' from the Left
43
*          = 'R': apply Q or Q' from the Right
44
*
45
*  TRANS   (input) CHARACTER*1
46
*          = 'N': apply Q  (No transpose)
47
*          = 'T': apply Q' (Transpose)
48
*
49
*  M       (input) INTEGER
50
*          The number of rows of the matrix C. M >= 0.
51
*
52
*  N       (input) INTEGER
53
*          The number of columns of the matrix C. N >= 0.
54
*
55
*  K       (input) INTEGER
56
*          The number of elementary reflectors whose product defines
57
*          the matrix Q.
58
*          If SIDE = 'L', M >= K >= 0;
59
*          if SIDE = 'R', N >= K >= 0.
60
*
61
*  L       (input) INTEGER
62
*          The number of columns of the matrix A containing
63
*          the meaningful part of the Householder reflectors.
64
*          If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
65
*
66
*  A       (input) DOUBLE PRECISION array, dimension
67
*                               (LDA,M) if SIDE = 'L',
68
*                               (LDA,N) if SIDE = 'R'
69
*          The i-th row must contain the vector which defines the
70
*          elementary reflector H(i), for i = 1,2,...,k, as returned by
71
*          DTZRZF in the last k rows of its array argument A.
72
*          A is modified by the routine but restored on exit.
73
*
74
*  LDA     (input) INTEGER
75
*          The leading dimension of the array A. LDA >= max(1,K).
76
*
77
*  TAU     (input) DOUBLE PRECISION array, dimension (K)
78
*          TAU(i) must contain the scalar factor of the elementary
79
*          reflector H(i), as returned by DTZRZF.
80
*
81
*  C       (input/output) DOUBLE PRECISION array, dimension (LDC,N)
82
*          On entry, the m-by-n matrix C.
83
*          On exit, C is overwritten by Q*C or Q'*C or C*Q' or C*Q.
84
*
85
*  LDC     (input) INTEGER
86
*          The leading dimension of the array C. LDC >= max(1,M).
87
*
88
*  WORK    (workspace) DOUBLE PRECISION array, dimension
89
*                                   (N) if SIDE = 'L',
90
*                                   (M) if SIDE = 'R'
91
*
92
*  INFO    (output) INTEGER
93
*          = 0: successful exit
94
*          < 0: if INFO = -i, the i-th argument had an illegal value
95
*
96
*  Further Details
97
*  ===============
98
*
99
*  Based on contributions by
100
*    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
101
*
102
*  =====================================================================
103
*
104
*     .. Local Scalars ..
105
      LOGICAL            LEFT, NOTRAN
106
      INTEGER            I, I1, I2, I3, IC, JA, JC, MI, NI, NQ
107
*     ..
108
*     .. External Functions ..
109
      LOGICAL            LSAME
110
      EXTERNAL           LSAME
111
*     ..
112
*     .. External Subroutines ..
113
      EXTERNAL           DLARZ, XERBLA
114
*     ..
115
*     .. Intrinsic Functions ..
116
      INTRINSIC          MAX
117
*     ..
118
*     .. Executable Statements ..
119
*
120
*     Test the input arguments
121
*
122
      INFO = 0
123
      LEFT = LSAME( SIDE, 'L' )
124
      NOTRAN = LSAME( TRANS, 'N' )
125
*
126
*     NQ is the order of Q
127
*
128
      IF( LEFT ) THEN
129
         NQ = M
130
      ELSE
131
         NQ = N
132
      END IF
133
      IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
134
         INFO = -1
135
      ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) ) THEN
136
         INFO = -2
137
      ELSE IF( M.LT.0 ) THEN
138
         INFO = -3
139
      ELSE IF( N.LT.0 ) THEN
140
         INFO = -4
141
      ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN
142
         INFO = -5
143
      ELSE IF( L.LT.0 .OR. ( LEFT .AND. ( L.GT.M ) ) .OR.
144
     $         ( .NOT.LEFT .AND. ( L.GT.N ) ) ) THEN
145
         INFO = -6
146
      ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
147
         INFO = -8
148
      ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
149
         INFO = -11
150
      END IF
151
      IF( INFO.NE.0 ) THEN
152
         CALL XERBLA( 'DORMR3', -INFO )
153
         RETURN
154
      END IF
155
*
156
*     Quick return if possible
157
*
158
      IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 )
159
     $   RETURN
160
*
161
      IF( ( LEFT .AND. .NOT.NOTRAN .OR. .NOT.LEFT .AND. NOTRAN ) ) THEN
162
         I1 = 1
163
         I2 = K
164
         I3 = 1
165
      ELSE
166
         I1 = K
167
         I2 = 1
168
         I3 = -1
169
      END IF
170
*
171
      IF( LEFT ) THEN
172
         NI = N
173
         JA = M - L + 1
174
         JC = 1
175
      ELSE
176
         MI = M
177
         JA = N - L + 1
178
         IC = 1
179
      END IF
180
*
181
      DO 10 I = I1, I2, I3
182
         IF( LEFT ) THEN
183
*
184
*           H(i) or H(i)' is applied to C(i:m,1:n)
185
*
186
            MI = M - I + 1
187
            IC = I
188
         ELSE
189
*
190
*           H(i) or H(i)' is applied to C(1:m,i:n)
191
*
192
            NI = N - I + 1
193
            JC = I
194
         END IF
195
*
196
*        Apply H(i) or H(i)'
197
*
198
         CALL DLARZ( SIDE, MI, NI, L, A( I, JA ), LDA, TAU( I ),
199
     $               C( IC, JC ), LDC, WORK )
200
*
201
   10 CONTINUE
202
*
203
      RETURN
204
*
205
*     End of DORMR3
206
*
207
      END