LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dopmtr ( character  SIDE,
character  UPLO,
character  TRANS,
integer  M,
integer  N,
double precision, dimension( * )  AP,
double precision, dimension( * )  TAU,
double precision, dimension( ldc, * )  C,
integer  LDC,
double precision, dimension( * )  WORK,
integer  INFO 
)

DOPMTR

Download DOPMTR + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DOPMTR overwrites the general real M-by-N matrix C with

                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      Q * C          C * Q
 TRANS = 'T':      Q**T * C       C * Q**T

 where Q is a real orthogonal matrix of order nq, with nq = m if
 SIDE = 'L' and nq = n if SIDE = 'R'. Q is defined as the product of
 nq-1 elementary reflectors, as returned by DSPTRD using packed
 storage:

 if UPLO = 'U', Q = H(nq-1) . . . H(2) H(1);

 if UPLO = 'L', Q = H(1) H(2) . . . H(nq-1).
Parameters
[in]SIDE
          SIDE is CHARACTER*1
          = 'L': apply Q or Q**T from the Left;
          = 'R': apply Q or Q**T from the Right.
[in]UPLO
          UPLO is CHARACTER*1
          = 'U': Upper triangular packed storage used in previous
                 call to DSPTRD;
          = 'L': Lower triangular packed storage used in previous
                 call to DSPTRD.
[in]TRANS
          TRANS is CHARACTER*1
          = 'N':  No transpose, apply Q;
          = 'T':  Transpose, apply Q**T.
[in]M
          M is INTEGER
          The number of rows of the matrix C. M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix C. N >= 0.
[in]AP
          AP is DOUBLE PRECISION array, dimension
                               (M*(M+1)/2) if SIDE = 'L'
                               (N*(N+1)/2) if SIDE = 'R'
          The vectors which define the elementary reflectors, as
          returned by DSPTRD.  AP is modified by the routine but
          restored on exit.
[in]TAU
          TAU is DOUBLE PRECISION array, dimension (M-1) if SIDE = 'L'
                                     or (N-1) if SIDE = 'R'
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by DSPTRD.
[in,out]C
          C is DOUBLE PRECISION array, dimension (LDC,N)
          On entry, the M-by-N matrix C.
          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C. LDC >= max(1,M).
[out]WORK
          WORK is DOUBLE PRECISION array, dimension
                                   (N) if SIDE = 'L'
                                   (M) if SIDE = 'R'
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 152 of file dopmtr.f.

152 *
153 * -- LAPACK computational routine (version 3.4.0) --
154 * -- LAPACK is a software package provided by Univ. of Tennessee, --
155 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156 * November 2011
157 *
158 * .. Scalar Arguments ..
159  CHARACTER side, trans, uplo
160  INTEGER info, ldc, m, n
161 * ..
162 * .. Array Arguments ..
163  DOUBLE PRECISION ap( * ), c( ldc, * ), tau( * ), work( * )
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Parameters ..
169  DOUBLE PRECISION one
170  parameter ( one = 1.0d+0 )
171 * ..
172 * .. Local Scalars ..
173  LOGICAL forwrd, left, notran, upper
174  INTEGER i, i1, i2, i3, ic, ii, jc, mi, ni, nq
175  DOUBLE PRECISION aii
176 * ..
177 * .. External Functions ..
178  LOGICAL lsame
179  EXTERNAL lsame
180 * ..
181 * .. External Subroutines ..
182  EXTERNAL dlarf, xerbla
183 * ..
184 * .. Intrinsic Functions ..
185  INTRINSIC max
186 * ..
187 * .. Executable Statements ..
188 *
189 * Test the input arguments
190 *
191  info = 0
192  left = lsame( side, 'L' )
193  notran = lsame( trans, 'N' )
194  upper = lsame( uplo, 'U' )
195 *
196 * NQ is the order of Q
197 *
198  IF( left ) THEN
199  nq = m
200  ELSE
201  nq = n
202  END IF
203  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
204  info = -1
205  ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
206  info = -2
207  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
208  info = -3
209  ELSE IF( m.LT.0 ) THEN
210  info = -4
211  ELSE IF( n.LT.0 ) THEN
212  info = -5
213  ELSE IF( ldc.LT.max( 1, m ) ) THEN
214  info = -9
215  END IF
216  IF( info.NE.0 ) THEN
217  CALL xerbla( 'DOPMTR', -info )
218  RETURN
219  END IF
220 *
221 * Quick return if possible
222 *
223  IF( m.EQ.0 .OR. n.EQ.0 )
224  $ RETURN
225 *
226  IF( upper ) THEN
227 *
228 * Q was determined by a call to DSPTRD with UPLO = 'U'
229 *
230  forwrd = ( left .AND. notran ) .OR.
231  $ ( .NOT.left .AND. .NOT.notran )
232 *
233  IF( forwrd ) THEN
234  i1 = 1
235  i2 = nq - 1
236  i3 = 1
237  ii = 2
238  ELSE
239  i1 = nq - 1
240  i2 = 1
241  i3 = -1
242  ii = nq*( nq+1 ) / 2 - 1
243  END IF
244 *
245  IF( left ) THEN
246  ni = n
247  ELSE
248  mi = m
249  END IF
250 *
251  DO 10 i = i1, i2, i3
252  IF( left ) THEN
253 *
254 * H(i) is applied to C(1:i,1:n)
255 *
256  mi = i
257  ELSE
258 *
259 * H(i) is applied to C(1:m,1:i)
260 *
261  ni = i
262  END IF
263 *
264 * Apply H(i)
265 *
266  aii = ap( ii )
267  ap( ii ) = one
268  CALL dlarf( side, mi, ni, ap( ii-i+1 ), 1, tau( i ), c, ldc,
269  $ work )
270  ap( ii ) = aii
271 *
272  IF( forwrd ) THEN
273  ii = ii + i + 2
274  ELSE
275  ii = ii - i - 1
276  END IF
277  10 CONTINUE
278  ELSE
279 *
280 * Q was determined by a call to DSPTRD with UPLO = 'L'.
281 *
282  forwrd = ( left .AND. .NOT.notran ) .OR.
283  $ ( .NOT.left .AND. notran )
284 *
285  IF( forwrd ) THEN
286  i1 = 1
287  i2 = nq - 1
288  i3 = 1
289  ii = 2
290  ELSE
291  i1 = nq - 1
292  i2 = 1
293  i3 = -1
294  ii = nq*( nq+1 ) / 2 - 1
295  END IF
296 *
297  IF( left ) THEN
298  ni = n
299  jc = 1
300  ELSE
301  mi = m
302  ic = 1
303  END IF
304 *
305  DO 20 i = i1, i2, i3
306  aii = ap( ii )
307  ap( ii ) = one
308  IF( left ) THEN
309 *
310 * H(i) is applied to C(i+1:m,1:n)
311 *
312  mi = m - i
313  ic = i + 1
314  ELSE
315 *
316 * H(i) is applied to C(1:m,i+1:n)
317 *
318  ni = n - i
319  jc = i + 1
320  END IF
321 *
322 * Apply H(i)
323 *
324  CALL dlarf( side, mi, ni, ap( ii ), 1, tau( i ),
325  $ c( ic, jc ), ldc, work )
326  ap( ii ) = aii
327 *
328  IF( forwrd ) THEN
329  ii = ii + nq - i + 1
330  ELSE
331  ii = ii - nq + i - 2
332  END IF
333  20 CONTINUE
334  END IF
335  RETURN
336 *
337 * End of DOPMTR
338 *
subroutine dlarf(SIDE, M, N, V, INCV, TAU, C, LDC, WORK)
DLARF applies an elementary reflector to a general rectangular matrix.
Definition: dlarf.f:126
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: