1818* Definition:
1919* ===========
2020*
21- * SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA , Q2, INDX,
21+ * SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMBDA , Q2, INDX,
2222* CTOT, W, S, INFO )
2323*
2424* .. Scalar Arguments ..
2727* ..
2828* .. Array Arguments ..
2929* INTEGER CTOT( * ), INDX( * )
30- * DOUBLE PRECISION D( * ), DLAMDA ( * ), Q( LDQ, * ), Q2( * ),
30+ * DOUBLE PRECISION D( * ), DLAMBDA ( * ), Q( LDQ, * ), Q2( * ),
3131* $ S( * ), W( * )
3232* ..
3333*
4444* > being combined by the matrix of eigenvectors of the K-by-K system
4545* > which is solved here.
4646* >
47- * > This code makes very mild assumptions about floating point
48- * > arithmetic. It will work on machines with a guard digit in
49- * > add/subtract, or on those binary machines without guard digits
50- * > which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or Cray-2.
51- * > It could conceivably fail on hexadecimal or decimal machines
52- * > without guard digits, but we know of none.
5347* > \endverbatim
5448*
5549* Arguments:
10498* > RHO >= 0 required.
10599* > \endverbatim
106100* >
107- * > \param[in,out] DLAMDA
101+ * > \param[in] DLAMBDA
108102* > \verbatim
109- * > DLAMDA is DOUBLE PRECISION array, dimension (K)
103+ * > DLAMBDA is DOUBLE PRECISION array, dimension (K)
110104* > The first K elements of this array contain the old roots
111105* > of the deflated updating problem. These are the poles
112- * > of the secular equation. May be changed on output by
113- * > having lowest order bit set to zero on Cray X-MP, Cray Y-MP,
114- * > Cray-2, or Cray C-90, as described above.
106+ * > of the secular equation.
115107* > \endverbatim
116108* >
117109* > \param[in] Q2
180172* > Modified by Francoise Tisseur, University of Tennessee
181173* >
182174* =====================================================================
183- SUBROUTINE DLAED3 ( K , N , N1 , D , Q , LDQ , RHO , DLAMDA , Q2 , INDX ,
175+ SUBROUTINE DLAED3 ( K , N , N1 , D , Q , LDQ , RHO , DLAMBDA , Q2 , INDX ,
184176 $ CTOT , W , S , INFO )
185177*
186178* -- LAPACK computational routine --
@@ -193,7 +185,7 @@ SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
193185* ..
194186* .. Array Arguments ..
195187 INTEGER CTOT( * ), INDX( * )
196- DOUBLE PRECISION D( * ), DLAMDA ( * ), Q( LDQ, * ), Q2( * ),
188+ DOUBLE PRECISION D( * ), DLAMBDA ( * ), Q( LDQ, * ), Q2( * ),
197189 $ S( * ), W( * )
198190* ..
199191*
@@ -208,8 +200,8 @@ SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
208200 DOUBLE PRECISION TEMP
209201* ..
210202* .. External Functions ..
211- DOUBLE PRECISION DLAMC3, DNRM2
212- EXTERNAL DLAMC3, DNRM2
203+ DOUBLE PRECISION DNRM2
204+ EXTERNAL DNRM2
213205* ..
214206* .. External Subroutines ..
215207 EXTERNAL DCOPY, DGEMM, DLACPY, DLAED4, DLASET, XERBLA
@@ -240,29 +232,9 @@ SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
240232 IF ( K.EQ. 0 )
241233 $ RETURN
242234*
243- * Modify values DLAMDA(i) to make sure all DLAMDA(i)-DLAMDA(j) can
244- * be computed with high relative accuracy (barring over/underflow).
245- * This is a problem on machines without a guard digit in
246- * add/subtract (Cray XMP, Cray YMP, Cray C 90 and Cray 2).
247- * The following code replaces DLAMDA(I) by 2*DLAMDA(I)-DLAMDA(I),
248- * which on any of these machines zeros out the bottommost
249- * bit of DLAMDA(I) if it is 1; this makes the subsequent
250- * subtractions DLAMDA(I)-DLAMDA(J) unproblematic when cancellation
251- * occurs. On binary machines with a guard digit (almost all
252- * machines) it does not change DLAMDA(I) at all. On hexadecimal
253- * and decimal machines with a guard digit, it slightly
254- * changes the bottommost bits of DLAMDA(I). It does not account
255- * for hexadecimal or decimal machines without guard digits
256- * (we know of none). We use a subroutine call to compute
257- * 2*DLAMBDA(I) to prevent optimizing compilers from eliminating
258- * this code.
259- *
260- DO 10 I = 1 , K
261- DLAMDA( I ) = DLAMC3( DLAMDA( I ), DLAMDA( I ) ) - DLAMDA( I )
262- 10 CONTINUE
263235*
264236 DO 20 J = 1 , K
265- CALL DLAED4( K, J, DLAMDA , W, Q( 1 , J ), RHO, D( J ), INFO )
237+ CALL DLAED4( K, J, DLAMBDA , W, Q( 1 , J ), RHO, D( J ), INFO )
266238*
267239* If the zero finder fails, the computation is terminated.
268240*
@@ -293,10 +265,10 @@ SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
293265 CALL DCOPY( K, Q, LDQ+1 , W, 1 )
294266 DO 60 J = 1 , K
295267 DO 40 I = 1 , J - 1
296- W( I ) = W( I )* ( Q( I, J ) / ( DLAMDA ( I )- DLAMDA ( J ) ) )
268+ W( I ) = W( I )* ( Q( I, J )/ ( DLAMBDA ( I )- DLAMBDA ( J ) ) )
297269 40 CONTINUE
298270 DO 50 I = J + 1 , K
299- W( I ) = W( I )* ( Q( I, J ) / ( DLAMDA ( I )- DLAMDA ( J ) ) )
271+ W( I ) = W( I )* ( Q( I, J )/ ( DLAMBDA ( I )- DLAMBDA ( J ) ) )
300272 50 CONTINUE
301273 60 CONTINUE
302274 DO 70 I = 1 , K
0 commit comments