LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dlaqr3.f
Go to the documentation of this file.
1 *> \brief \b DLAQR3 performs the orthogonal similarity transformation of a Hessenberg matrix to detect and deflate fully converged eigenvalues from a trailing principal submatrix (aggressive early deflation).
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DLAQR3 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaqr3.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaqr3.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaqr3.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DLAQR3( WANTT, WANTZ, N, KTOP, KBOT, NW, H, LDH, ILOZ,
22 * IHIZ, Z, LDZ, NS, ND, SR, SI, V, LDV, NH, T,
23 * LDT, NV, WV, LDWV, WORK, LWORK )
24 *
25 * .. Scalar Arguments ..
26 * INTEGER IHIZ, ILOZ, KBOT, KTOP, LDH, LDT, LDV, LDWV,
27 * $ LDZ, LWORK, N, ND, NH, NS, NV, NW
28 * LOGICAL WANTT, WANTZ
29 * ..
30 * .. Array Arguments ..
31 * DOUBLE PRECISION H( LDH, * ), SI( * ), SR( * ), T( LDT, * ),
32 * $ V( LDV, * ), WORK( * ), WV( LDWV, * ),
33 * $ Z( LDZ, * )
34 * ..
35 *
36 *
37 *> \par Purpose:
38 * =============
39 *>
40 *> \verbatim
41 *>
42 *> Aggressive early deflation:
43 *>
44 *> DLAQR3 accepts as input an upper Hessenberg matrix
45 *> H and performs an orthogonal similarity transformation
46 *> designed to detect and deflate fully converged eigenvalues from
47 *> a trailing principal submatrix. On output H has been over-
48 *> written by a new Hessenberg matrix that is a perturbation of
49 *> an orthogonal similarity transformation of H. It is to be
50 *> hoped that the final version of H has many zero subdiagonal
51 *> entries.
52 *> \endverbatim
53 *
54 * Arguments:
55 * ==========
56 *
57 *> \param[in] WANTT
58 *> \verbatim
59 *> WANTT is LOGICAL
60 *> If .TRUE., then the Hessenberg matrix H is fully updated
61 *> so that the quasi-triangular Schur factor may be
62 *> computed (in cooperation with the calling subroutine).
63 *> If .FALSE., then only enough of H is updated to preserve
64 *> the eigenvalues.
65 *> \endverbatim
66 *>
67 *> \param[in] WANTZ
68 *> \verbatim
69 *> WANTZ is LOGICAL
70 *> If .TRUE., then the orthogonal matrix Z is updated so
71 *> so that the orthogonal Schur factor may be computed
72 *> (in cooperation with the calling subroutine).
73 *> If .FALSE., then Z is not referenced.
74 *> \endverbatim
75 *>
76 *> \param[in] N
77 *> \verbatim
78 *> N is INTEGER
79 *> The order of the matrix H and (if WANTZ is .TRUE.) the
80 *> order of the orthogonal matrix Z.
81 *> \endverbatim
82 *>
83 *> \param[in] KTOP
84 *> \verbatim
85 *> KTOP is INTEGER
86 *> It is assumed that either KTOP = 1 or H(KTOP,KTOP-1)=0.
87 *> KBOT and KTOP together determine an isolated block
88 *> along the diagonal of the Hessenberg matrix.
89 *> \endverbatim
90 *>
91 *> \param[in] KBOT
92 *> \verbatim
93 *> KBOT is INTEGER
94 *> It is assumed without a check that either
95 *> KBOT = N or H(KBOT+1,KBOT)=0. KBOT and KTOP together
96 *> determine an isolated block along the diagonal of the
97 *> Hessenberg matrix.
98 *> \endverbatim
99 *>
100 *> \param[in] NW
101 *> \verbatim
102 *> NW is INTEGER
103 *> Deflation window size. 1 .LE. NW .LE. (KBOT-KTOP+1).
104 *> \endverbatim
105 *>
106 *> \param[in,out] H
107 *> \verbatim
108 *> H is DOUBLE PRECISION array, dimension (LDH,N)
109 *> On input the initial N-by-N section of H stores the
110 *> Hessenberg matrix undergoing aggressive early deflation.
111 *> On output H has been transformed by an orthogonal
112 *> similarity transformation, perturbed, and the returned
113 *> to Hessenberg form that (it is to be hoped) has some
114 *> zero subdiagonal entries.
115 *> \endverbatim
116 *>
117 *> \param[in] LDH
118 *> \verbatim
119 *> LDH is integer
120 *> Leading dimension of H just as declared in the calling
121 *> subroutine. N .LE. LDH
122 *> \endverbatim
123 *>
124 *> \param[in] ILOZ
125 *> \verbatim
126 *> ILOZ is INTEGER
127 *> \endverbatim
128 *>
129 *> \param[in] IHIZ
130 *> \verbatim
131 *> IHIZ is INTEGER
132 *> Specify the rows of Z to which transformations must be
133 *> applied if WANTZ is .TRUE.. 1 .LE. ILOZ .LE. IHIZ .LE. N.
134 *> \endverbatim
135 *>
136 *> \param[in,out] Z
137 *> \verbatim
138 *> Z is DOUBLE PRECISION array, dimension (LDZ,N)
139 *> IF WANTZ is .TRUE., then on output, the orthogonal
140 *> similarity transformation mentioned above has been
141 *> accumulated into Z(ILOZ:IHIZ,ILOZ:IHIZ) from the right.
142 *> If WANTZ is .FALSE., then Z is unreferenced.
143 *> \endverbatim
144 *>
145 *> \param[in] LDZ
146 *> \verbatim
147 *> LDZ is integer
148 *> The leading dimension of Z just as declared in the
149 *> calling subroutine. 1 .LE. LDZ.
150 *> \endverbatim
151 *>
152 *> \param[out] NS
153 *> \verbatim
154 *> NS is integer
155 *> The number of unconverged (ie approximate) eigenvalues
156 *> returned in SR and SI that may be used as shifts by the
157 *> calling subroutine.
158 *> \endverbatim
159 *>
160 *> \param[out] ND
161 *> \verbatim
162 *> ND is integer
163 *> The number of converged eigenvalues uncovered by this
164 *> subroutine.
165 *> \endverbatim
166 *>
167 *> \param[out] SR
168 *> \verbatim
169 *> SR is DOUBLE PRECISION array, dimension (KBOT)
170 *> \endverbatim
171 *>
172 *> \param[out] SI
173 *> \verbatim
174 *> SI is DOUBLE PRECISION array, dimension (KBOT)
175 *> On output, the real and imaginary parts of approximate
176 *> eigenvalues that may be used for shifts are stored in
177 *> SR(KBOT-ND-NS+1) through SR(KBOT-ND) and
178 *> SI(KBOT-ND-NS+1) through SI(KBOT-ND), respectively.
179 *> The real and imaginary parts of converged eigenvalues
180 *> are stored in SR(KBOT-ND+1) through SR(KBOT) and
181 *> SI(KBOT-ND+1) through SI(KBOT), respectively.
182 *> \endverbatim
183 *>
184 *> \param[out] V
185 *> \verbatim
186 *> V is DOUBLE PRECISION array, dimension (LDV,NW)
187 *> An NW-by-NW work array.
188 *> \endverbatim
189 *>
190 *> \param[in] LDV
191 *> \verbatim
192 *> LDV is integer scalar
193 *> The leading dimension of V just as declared in the
194 *> calling subroutine. NW .LE. LDV
195 *> \endverbatim
196 *>
197 *> \param[in] NH
198 *> \verbatim
199 *> NH is integer scalar
200 *> The number of columns of T. NH.GE.NW.
201 *> \endverbatim
202 *>
203 *> \param[out] T
204 *> \verbatim
205 *> T is DOUBLE PRECISION array, dimension (LDT,NW)
206 *> \endverbatim
207 *>
208 *> \param[in] LDT
209 *> \verbatim
210 *> LDT is integer
211 *> The leading dimension of T just as declared in the
212 *> calling subroutine. NW .LE. LDT
213 *> \endverbatim
214 *>
215 *> \param[in] NV
216 *> \verbatim
217 *> NV is integer
218 *> The number of rows of work array WV available for
219 *> workspace. NV.GE.NW.
220 *> \endverbatim
221 *>
222 *> \param[out] WV
223 *> \verbatim
224 *> WV is DOUBLE PRECISION array, dimension (LDWV,NW)
225 *> \endverbatim
226 *>
227 *> \param[in] LDWV
228 *> \verbatim
229 *> LDWV is integer
230 *> The leading dimension of W just as declared in the
231 *> calling subroutine. NW .LE. LDV
232 *> \endverbatim
233 *>
234 *> \param[out] WORK
235 *> \verbatim
236 *> WORK is DOUBLE PRECISION array, dimension (LWORK)
237 *> On exit, WORK(1) is set to an estimate of the optimal value
238 *> of LWORK for the given values of N, NW, KTOP and KBOT.
239 *> \endverbatim
240 *>
241 *> \param[in] LWORK
242 *> \verbatim
243 *> LWORK is integer
244 *> The dimension of the work array WORK. LWORK = 2*NW
245 *> suffices, but greater efficiency may result from larger
246 *> values of LWORK.
247 *>
248 *> If LWORK = -1, then a workspace query is assumed; DLAQR3
249 *> only estimates the optimal workspace size for the given
250 *> values of N, NW, KTOP and KBOT. The estimate is returned
251 *> in WORK(1). No error message related to LWORK is issued
252 *> by XERBLA. Neither H nor Z are accessed.
253 *> \endverbatim
254 *
255 * Authors:
256 * ========
257 *
258 *> \author Univ. of Tennessee
259 *> \author Univ. of California Berkeley
260 *> \author Univ. of Colorado Denver
261 *> \author NAG Ltd.
262 *
263 *> \date June 2016
264 *
265 *> \ingroup doubleOTHERauxiliary
266 *
267 *> \par Contributors:
268 * ==================
269 *>
270 *> Karen Braman and Ralph Byers, Department of Mathematics,
271 *> University of Kansas, USA
272 *>
273 * =====================================================================
274  SUBROUTINE dlaqr3( WANTT, WANTZ, N, KTOP, KBOT, NW, H, LDH, ILOZ,
275  $ ihiz, z, ldz, ns, nd, sr, si, v, ldv, nh, t,
276  $ ldt, nv, wv, ldwv, work, lwork )
277 *
278 * -- LAPACK auxiliary routine (version 3.6.1) --
279 * -- LAPACK is a software package provided by Univ. of Tennessee, --
280 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
281 * June 2016
282 *
283 * .. Scalar Arguments ..
284  INTEGER IHIZ, ILOZ, KBOT, KTOP, LDH, LDT, LDV, LDWV,
285  $ ldz, lwork, n, nd, nh, ns, nv, nw
286  LOGICAL WANTT, WANTZ
287 * ..
288 * .. Array Arguments ..
289  DOUBLE PRECISION H( ldh, * ), SI( * ), SR( * ), T( ldt, * ),
290  $ v( ldv, * ), work( * ), wv( ldwv, * ),
291  $ z( ldz, * )
292 * ..
293 *
294 * ================================================================
295 * .. Parameters ..
296  DOUBLE PRECISION ZERO, ONE
297  parameter ( zero = 0.0d0, one = 1.0d0 )
298 * ..
299 * .. Local Scalars ..
300  DOUBLE PRECISION AA, BB, BETA, CC, CS, DD, EVI, EVK, FOO, S,
301  $ safmax, safmin, smlnum, sn, tau, ulp
302  INTEGER I, IFST, ILST, INFO, INFQR, J, JW, K, KCOL,
303  $ kend, kln, krow, kwtop, ltop, lwk1, lwk2, lwk3,
304  $ lwkopt, nmin
305  LOGICAL BULGE, SORTED
306 * ..
307 * .. External Functions ..
308  DOUBLE PRECISION DLAMCH
309  INTEGER ILAENV
310  EXTERNAL dlamch, ilaenv
311 * ..
312 * .. External Subroutines ..
313  EXTERNAL dcopy, dgehrd, dgemm, dlabad, dlacpy, dlahqr,
315  $ dtrexc
316 * ..
317 * .. Intrinsic Functions ..
318  INTRINSIC abs, dble, int, max, min, sqrt
319 * ..
320 * .. Executable Statements ..
321 *
322 * ==== Estimate optimal workspace. ====
323 *
324  jw = min( nw, kbot-ktop+1 )
325  IF( jw.LE.2 ) THEN
326  lwkopt = 1
327  ELSE
328 *
329 * ==== Workspace query call to DGEHRD ====
330 *
331  CALL dgehrd( jw, 1, jw-1, t, ldt, work, work, -1, info )
332  lwk1 = int( work( 1 ) )
333 *
334 * ==== Workspace query call to DORMHR ====
335 *
336  CALL dormhr( 'R', 'N', jw, jw, 1, jw-1, t, ldt, work, v, ldv,
337  $ work, -1, info )
338  lwk2 = int( work( 1 ) )
339 *
340 * ==== Workspace query call to DLAQR4 ====
341 *
342  CALL dlaqr4( .true., .true., jw, 1, jw, t, ldt, sr, si, 1, jw,
343  $ v, ldv, work, -1, infqr )
344  lwk3 = int( work( 1 ) )
345 *
346 * ==== Optimal workspace ====
347 *
348  lwkopt = max( jw+max( lwk1, lwk2 ), lwk3 )
349  END IF
350 *
351 * ==== Quick return in case of workspace query. ====
352 *
353  IF( lwork.EQ.-1 ) THEN
354  work( 1 ) = dble( lwkopt )
355  RETURN
356  END IF
357 *
358 * ==== Nothing to do ...
359 * ... for an empty active block ... ====
360  ns = 0
361  nd = 0
362  work( 1 ) = one
363  IF( ktop.GT.kbot )
364  $ RETURN
365 * ... nor for an empty deflation window. ====
366  IF( nw.LT.1 )
367  $ RETURN
368 *
369 * ==== Machine constants ====
370 *
371  safmin = dlamch( 'SAFE MINIMUM' )
372  safmax = one / safmin
373  CALL dlabad( safmin, safmax )
374  ulp = dlamch( 'PRECISION' )
375  smlnum = safmin*( dble( n ) / ulp )
376 *
377 * ==== Setup deflation window ====
378 *
379  jw = min( nw, kbot-ktop+1 )
380  kwtop = kbot - jw + 1
381  IF( kwtop.EQ.ktop ) THEN
382  s = zero
383  ELSE
384  s = h( kwtop, kwtop-1 )
385  END IF
386 *
387  IF( kbot.EQ.kwtop ) THEN
388 *
389 * ==== 1-by-1 deflation window: not much to do ====
390 *
391  sr( kwtop ) = h( kwtop, kwtop )
392  si( kwtop ) = zero
393  ns = 1
394  nd = 0
395  IF( abs( s ).LE.max( smlnum, ulp*abs( h( kwtop, kwtop ) ) ) )
396  $ THEN
397  ns = 0
398  nd = 1
399  IF( kwtop.GT.ktop )
400  $ h( kwtop, kwtop-1 ) = zero
401  END IF
402  work( 1 ) = one
403  RETURN
404  END IF
405 *
406 * ==== Convert to spike-triangular form. (In case of a
407 * . rare QR failure, this routine continues to do
408 * . aggressive early deflation using that part of
409 * . the deflation window that converged using INFQR
410 * . here and there to keep track.) ====
411 *
412  CALL dlacpy( 'U', jw, jw, h( kwtop, kwtop ), ldh, t, ldt )
413  CALL dcopy( jw-1, h( kwtop+1, kwtop ), ldh+1, t( 2, 1 ), ldt+1 )
414 *
415  CALL dlaset( 'A', jw, jw, zero, one, v, ldv )
416  nmin = ilaenv( 12, 'DLAQR3', 'SV', jw, 1, jw, lwork )
417  IF( jw.GT.nmin ) THEN
418  CALL dlaqr4( .true., .true., jw, 1, jw, t, ldt, sr( kwtop ),
419  $ si( kwtop ), 1, jw, v, ldv, work, lwork, infqr )
420  ELSE
421  CALL dlahqr( .true., .true., jw, 1, jw, t, ldt, sr( kwtop ),
422  $ si( kwtop ), 1, jw, v, ldv, infqr )
423  END IF
424 *
425 * ==== DTREXC needs a clean margin near the diagonal ====
426 *
427  DO 10 j = 1, jw - 3
428  t( j+2, j ) = zero
429  t( j+3, j ) = zero
430  10 CONTINUE
431  IF( jw.GT.2 )
432  $ t( jw, jw-2 ) = zero
433 *
434 * ==== Deflation detection loop ====
435 *
436  ns = jw
437  ilst = infqr + 1
438  20 CONTINUE
439  IF( ilst.LE.ns ) THEN
440  IF( ns.EQ.1 ) THEN
441  bulge = .false.
442  ELSE
443  bulge = t( ns, ns-1 ).NE.zero
444  END IF
445 *
446 * ==== Small spike tip test for deflation ====
447 *
448  IF( .NOT. bulge ) THEN
449 *
450 * ==== Real eigenvalue ====
451 *
452  foo = abs( t( ns, ns ) )
453  IF( foo.EQ.zero )
454  $ foo = abs( s )
455  IF( abs( s*v( 1, ns ) ).LE.max( smlnum, ulp*foo ) ) THEN
456 *
457 * ==== Deflatable ====
458 *
459  ns = ns - 1
460  ELSE
461 *
462 * ==== Undeflatable. Move it up out of the way.
463 * . (DTREXC can not fail in this case.) ====
464 *
465  ifst = ns
466  CALL dtrexc( 'V', jw, t, ldt, v, ldv, ifst, ilst, work,
467  $ info )
468  ilst = ilst + 1
469  END IF
470  ELSE
471 *
472 * ==== Complex conjugate pair ====
473 *
474  foo = abs( t( ns, ns ) ) + sqrt( abs( t( ns, ns-1 ) ) )*
475  $ sqrt( abs( t( ns-1, ns ) ) )
476  IF( foo.EQ.zero )
477  $ foo = abs( s )
478  IF( max( abs( s*v( 1, ns ) ), abs( s*v( 1, ns-1 ) ) ).LE.
479  $ max( smlnum, ulp*foo ) ) THEN
480 *
481 * ==== Deflatable ====
482 *
483  ns = ns - 2
484  ELSE
485 *
486 * ==== Undeflatable. Move them up out of the way.
487 * . Fortunately, DTREXC does the right thing with
488 * . ILST in case of a rare exchange failure. ====
489 *
490  ifst = ns
491  CALL dtrexc( 'V', jw, t, ldt, v, ldv, ifst, ilst, work,
492  $ info )
493  ilst = ilst + 2
494  END IF
495  END IF
496 *
497 * ==== End deflation detection loop ====
498 *
499  GO TO 20
500  END IF
501 *
502 * ==== Return to Hessenberg form ====
503 *
504  IF( ns.EQ.0 )
505  $ s = zero
506 *
507  IF( ns.LT.jw ) THEN
508 *
509 * ==== sorting diagonal blocks of T improves accuracy for
510 * . graded matrices. Bubble sort deals well with
511 * . exchange failures. ====
512 *
513  sorted = .false.
514  i = ns + 1
515  30 CONTINUE
516  IF( sorted )
517  $ GO TO 50
518  sorted = .true.
519 *
520  kend = i - 1
521  i = infqr + 1
522  IF( i.EQ.ns ) THEN
523  k = i + 1
524  ELSE IF( t( i+1, i ).EQ.zero ) THEN
525  k = i + 1
526  ELSE
527  k = i + 2
528  END IF
529  40 CONTINUE
530  IF( k.LE.kend ) THEN
531  IF( k.EQ.i+1 ) THEN
532  evi = abs( t( i, i ) )
533  ELSE
534  evi = abs( t( i, i ) ) + sqrt( abs( t( i+1, i ) ) )*
535  $ sqrt( abs( t( i, i+1 ) ) )
536  END IF
537 *
538  IF( k.EQ.kend ) THEN
539  evk = abs( t( k, k ) )
540  ELSE IF( t( k+1, k ).EQ.zero ) THEN
541  evk = abs( t( k, k ) )
542  ELSE
543  evk = abs( t( k, k ) ) + sqrt( abs( t( k+1, k ) ) )*
544  $ sqrt( abs( t( k, k+1 ) ) )
545  END IF
546 *
547  IF( evi.GE.evk ) THEN
548  i = k
549  ELSE
550  sorted = .false.
551  ifst = i
552  ilst = k
553  CALL dtrexc( 'V', jw, t, ldt, v, ldv, ifst, ilst, work,
554  $ info )
555  IF( info.EQ.0 ) THEN
556  i = ilst
557  ELSE
558  i = k
559  END IF
560  END IF
561  IF( i.EQ.kend ) THEN
562  k = i + 1
563  ELSE IF( t( i+1, i ).EQ.zero ) THEN
564  k = i + 1
565  ELSE
566  k = i + 2
567  END IF
568  GO TO 40
569  END IF
570  GO TO 30
571  50 CONTINUE
572  END IF
573 *
574 * ==== Restore shift/eigenvalue array from T ====
575 *
576  i = jw
577  60 CONTINUE
578  IF( i.GE.infqr+1 ) THEN
579  IF( i.EQ.infqr+1 ) THEN
580  sr( kwtop+i-1 ) = t( i, i )
581  si( kwtop+i-1 ) = zero
582  i = i - 1
583  ELSE IF( t( i, i-1 ).EQ.zero ) THEN
584  sr( kwtop+i-1 ) = t( i, i )
585  si( kwtop+i-1 ) = zero
586  i = i - 1
587  ELSE
588  aa = t( i-1, i-1 )
589  cc = t( i, i-1 )
590  bb = t( i-1, i )
591  dd = t( i, i )
592  CALL dlanv2( aa, bb, cc, dd, sr( kwtop+i-2 ),
593  $ si( kwtop+i-2 ), sr( kwtop+i-1 ),
594  $ si( kwtop+i-1 ), cs, sn )
595  i = i - 2
596  END IF
597  GO TO 60
598  END IF
599 *
600  IF( ns.LT.jw .OR. s.EQ.zero ) THEN
601  IF( ns.GT.1 .AND. s.NE.zero ) THEN
602 *
603 * ==== Reflect spike back into lower triangle ====
604 *
605  CALL dcopy( ns, v, ldv, work, 1 )
606  beta = work( 1 )
607  CALL dlarfg( ns, beta, work( 2 ), 1, tau )
608  work( 1 ) = one
609 *
610  CALL dlaset( 'L', jw-2, jw-2, zero, zero, t( 3, 1 ), ldt )
611 *
612  CALL dlarf( 'L', ns, jw, work, 1, tau, t, ldt,
613  $ work( jw+1 ) )
614  CALL dlarf( 'R', ns, ns, work, 1, tau, t, ldt,
615  $ work( jw+1 ) )
616  CALL dlarf( 'R', jw, ns, work, 1, tau, v, ldv,
617  $ work( jw+1 ) )
618 *
619  CALL dgehrd( jw, 1, ns, t, ldt, work, work( jw+1 ),
620  $ lwork-jw, info )
621  END IF
622 *
623 * ==== Copy updated reduced window into place ====
624 *
625  IF( kwtop.GT.1 )
626  $ h( kwtop, kwtop-1 ) = s*v( 1, 1 )
627  CALL dlacpy( 'U', jw, jw, t, ldt, h( kwtop, kwtop ), ldh )
628  CALL dcopy( jw-1, t( 2, 1 ), ldt+1, h( kwtop+1, kwtop ),
629  $ ldh+1 )
630 *
631 * ==== Accumulate orthogonal matrix in order update
632 * . H and Z, if requested. ====
633 *
634  IF( ns.GT.1 .AND. s.NE.zero )
635  $ CALL dormhr( 'R', 'N', jw, ns, 1, ns, t, ldt, work, v, ldv,
636  $ work( jw+1 ), lwork-jw, info )
637 *
638 * ==== Update vertical slab in H ====
639 *
640  IF( wantt ) THEN
641  ltop = 1
642  ELSE
643  ltop = ktop
644  END IF
645  DO 70 krow = ltop, kwtop - 1, nv
646  kln = min( nv, kwtop-krow )
647  CALL dgemm( 'N', 'N', kln, jw, jw, one, h( krow, kwtop ),
648  $ ldh, v, ldv, zero, wv, ldwv )
649  CALL dlacpy( 'A', kln, jw, wv, ldwv, h( krow, kwtop ), ldh )
650  70 CONTINUE
651 *
652 * ==== Update horizontal slab in H ====
653 *
654  IF( wantt ) THEN
655  DO 80 kcol = kbot + 1, n, nh
656  kln = min( nh, n-kcol+1 )
657  CALL dgemm( 'C', 'N', jw, kln, jw, one, v, ldv,
658  $ h( kwtop, kcol ), ldh, zero, t, ldt )
659  CALL dlacpy( 'A', jw, kln, t, ldt, h( kwtop, kcol ),
660  $ ldh )
661  80 CONTINUE
662  END IF
663 *
664 * ==== Update vertical slab in Z ====
665 *
666  IF( wantz ) THEN
667  DO 90 krow = iloz, ihiz, nv
668  kln = min( nv, ihiz-krow+1 )
669  CALL dgemm( 'N', 'N', kln, jw, jw, one, z( krow, kwtop ),
670  $ ldz, v, ldv, zero, wv, ldwv )
671  CALL dlacpy( 'A', kln, jw, wv, ldwv, z( krow, kwtop ),
672  $ ldz )
673  90 CONTINUE
674  END IF
675  END IF
676 *
677 * ==== Return the number of deflations ... ====
678 *
679  nd = jw - ns
680 *
681 * ==== ... and the number of shifts. (Subtracting
682 * . INFQR from the spike length takes care
683 * . of the case of a rare QR failure while
684 * . calculating eigenvalues of the deflation
685 * . window.) ====
686 *
687  ns = ns - infqr
688 *
689 * ==== Return optimal workspace. ====
690 *
691  work( 1 ) = dble( lwkopt )
692 *
693 * ==== End of DLAQR3 ====
694 *
695  END
subroutine dlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: dlaset.f:112
subroutine dcopy(N, DX, INCX, DY, INCY)
DCOPY
Definition: dcopy.f:53
subroutine dtrexc(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, WORK, INFO)
DTREXC
Definition: dtrexc.f:148
subroutine dlacpy(UPLO, M, N, A, LDA, B, LDB)
DLACPY copies all or part of one two-dimensional array to another.
Definition: dlacpy.f:105
subroutine dgehrd(N, ILO, IHI, A, LDA, TAU, WORK, LWORK, INFO)
DGEHRD
Definition: dgehrd.f:169
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 dlahqr(WANTT, WANTZ, N, ILO, IHI, H, LDH, WR, WI, ILOZ, IHIZ, Z, LDZ, INFO)
DLAHQR computes the eigenvalues and Schur factorization of an upper Hessenberg matrix, using the double-shift/single-shift QR algorithm.
Definition: dlahqr.f:209
subroutine dgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
DGEMM
Definition: dgemm.f:189
subroutine dlabad(SMALL, LARGE)
DLABAD
Definition: dlabad.f:76
subroutine dlaqr3(WANTT, WANTZ, N, KTOP, KBOT, NW, H, LDH, ILOZ, IHIZ, Z, LDZ, NS, ND, SR, SI, V, LDV, NH, T, LDT, NV, WV, LDWV, WORK, LWORK)
DLAQR3 performs the orthogonal similarity transformation of a Hessenberg matrix to detect and deflate...
Definition: dlaqr3.f:277
subroutine dlarfg(N, ALPHA, X, INCX, TAU)
DLARFG generates an elementary reflector (Householder matrix).
Definition: dlarfg.f:108
subroutine dlaqr4(WANTT, WANTZ, N, ILO, IHI, H, LDH, WR, WI, ILOZ, IHIZ, Z, LDZ, WORK, LWORK, INFO)
DLAQR4 computes the eigenvalues of a Hessenberg matrix, and optionally the matrices from the Schur de...
Definition: dlaqr4.f:265
subroutine dormhr(SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
DORMHR
Definition: dormhr.f:180
subroutine dlanv2(A, B, C, D, RT1R, RT1I, RT2R, RT2I, CS, SN)
DLANV2 computes the Schur factorization of a real 2-by-2 nonsymmetric matrix in standard form...
Definition: dlanv2.f:129