📄 pdsteqr.f
字号:
* ELSE** Use Selection Sort to minimize swaps of eigenvectors* DO 180 II = 2, N I = II - 1 K = I P = D( I ) DO 170 J = II, N IF( D( J ).LT.P ) THEN K = J P = D( J ) END IF 170 CONTINUE IF( K.NE.I ) THEN D( K ) = D( I ) D( I ) = P CALL DSWAP( nz, Z( 1, I ), 1, Z( 1, K ), 1 ) END IF 180 CONTINUE END IF* 190 CONTINUE RETURN** End of DSTEQR* END* Auxiliary routines are not provided with all commerical lapacks,* so a local copy for use by PDSTEQR is provided here. SUBROUTINE PDLAE2( A, B, C, RT1, RT2 )** -- LAPACK auxiliary routine (version 3.0) --* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,* Courant Institute, Argonne National Lab, and Rice University* October 31, 1992** .. Scalar Arguments .. DOUBLE PRECISION A, B, C, RT1, RT2* ..** Purpose* =======** DLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix* [ A B ]* [ B C ].* On return, RT1 is the eigenvalue of larger absolute value, and RT2* is the eigenvalue of smaller absolute value.** Arguments* =========** A (input) DOUBLE PRECISION* The (1,1) element of the 2-by-2 matrix.** B (input) DOUBLE PRECISION* The (1,2) and (2,1) elements of the 2-by-2 matrix.** C (input) DOUBLE PRECISION* The (2,2) element of the 2-by-2 matrix.** RT1 (output) DOUBLE PRECISION* The eigenvalue of larger absolute value.** RT2 (output) DOUBLE PRECISION* The eigenvalue of smaller absolute value.** Further Details* ===============** RT1 is accurate to a few ulps barring over/underflow.** RT2 may be inaccurate if there is massive cancellation in the* determinant A*C-B*B; higher precision or correctly rounded or* correctly truncated arithmetic would be needed to compute RT2* accurately in all cases.** Overflow is possible only if RT1 is within a factor of 5 of overflow.* Underflow is harmless if the input data is 0 or exceeds* underflow_threshold / macheps.** =====================================================================** .. Parameters .. DOUBLE PRECISION ONE PARAMETER ( ONE = 1.0D0 ) DOUBLE PRECISION TWO PARAMETER ( TWO = 2.0D0 ) DOUBLE PRECISION ZERO PARAMETER ( ZERO = 0.0D0 ) DOUBLE PRECISION HALF PARAMETER ( HALF = 0.5D0 )* ..* .. Local Scalars .. DOUBLE PRECISION AB, ACMN, ACMX, ADF, DF, RT, SM, TB* ..* .. Intrinsic Functions .. INTRINSIC ABS, SQRT* ..* .. Executable Statements ..** Compute the eigenvalues* SM = A + C DF = A - C ADF = ABS( DF ) TB = B + B AB = ABS( TB ) IF( ABS( A ).GT.ABS( C ) ) THEN ACMX = A ACMN = C ELSE ACMX = C ACMN = A END IF IF( ADF.GT.AB ) THEN RT = ADF*SQRT( ONE+( AB / ADF )**2 ) ELSE IF( ADF.LT.AB ) THEN RT = AB*SQRT( ONE+( ADF / AB )**2 ) ELSE** Includes case AB=ADF=0* RT = AB*SQRT( TWO ) END IF IF( SM.LT.ZERO ) THEN RT1 = HALF*( SM-RT )** Order of execution important.* To get fully accurate smaller eigenvalue,* next line needs to be executed in higher precision.* RT2 = ( ACMX / RT1 )*ACMN - ( B / RT1 )*B ELSE IF( SM.GT.ZERO ) THEN RT1 = HALF*( SM+RT )** Order of execution important.* To get fully accurate smaller eigenvalue,* next line needs to be executed in higher precision.* RT2 = ( ACMX / RT1 )*ACMN - ( B / RT1 )*B ELSE** Includes case RT1 = RT2 = 0* RT1 = HALF*RT RT2 = -HALF*RT END IF RETURN** End of DLAE2* END SUBROUTINE PDLAEV2( A, B, C, RT1, RT2, CS1, SN1 )** -- LAPACK auxiliary routine (version 3.0) --* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,* Courant Institute, Argonne National Lab, and Rice University* October 31, 1992** .. Scalar Arguments .. DOUBLE PRECISION A, B, C, CS1, RT1, RT2, SN1* ..** Purpose* =======** DLAEV2 computes the eigendecomposition of a 2-by-2 symmetric matrix* [ A B ]* [ B C ].* On return, RT1 is the eigenvalue of larger absolute value, RT2 is the* eigenvalue of smaller absolute value, and (CS1,SN1) is the unit right* eigenvector for RT1, giving the decomposition** [ CS1 SN1 ] [ A B ] [ CS1 -SN1 ] = [ RT1 0 ]* [-SN1 CS1 ] [ B C ] [ SN1 CS1 ] [ 0 RT2 ].** Arguments* =========** A (input) DOUBLE PRECISION* The (1,1) element of the 2-by-2 matrix.** B (input) DOUBLE PRECISION* The (1,2) element and the conjugate of the (2,1) element of* the 2-by-2 matrix.** C (input) DOUBLE PRECISION* The (2,2) element of the 2-by-2 matrix.** RT1 (output) DOUBLE PRECISION* The eigenvalue of larger absolute value.** RT2 (output) DOUBLE PRECISION* The eigenvalue of smaller absolute value.** CS1 (output) DOUBLE PRECISION* SN1 (output) DOUBLE PRECISION* The vector (CS1, SN1) is a unit right eigenvector for RT1.** Further Details* ===============** RT1 is accurate to a few ulps barring over/underflow.** RT2 may be inaccurate if there is massive cancellation in the* determinant A*C-B*B; higher precision or correctly rounded or* correctly truncated arithmetic would be needed to compute RT2* accurately in all cases.** CS1 and SN1 are accurate to a few ulps barring over/underflow.** Overflow is possible only if RT1 is within a factor of 5 of overflow.* Underflow is harmless if the input data is 0 or exceeds* underflow_threshold / macheps.** =====================================================================** .. Parameters .. DOUBLE PRECISION ONE PARAMETER ( ONE = 1.0D0 ) DOUBLE PRECISION TWO PARAMETER ( TWO = 2.0D0 ) DOUBLE PRECISION ZERO PARAMETER ( ZERO = 0.0D0 ) DOUBLE PRECISION HALF PARAMETER ( HALF = 0.5D0 )* ..* .. Local Scalars .. INTEGER SGN1, SGN2 DOUBLE PRECISION AB, ACMN, ACMX, ACS, ADF, CS, CT, DF, RT, SM, $ TB, TN* ..* .. Intrinsic Functions .. INTRINSIC ABS, SQRT* ..* .. Executable Statements ..** Compute the eigenvalues* SM = A + C DF = A - C ADF = ABS( DF ) TB = B + B AB = ABS( TB ) IF( ABS( A ).GT.ABS( C ) ) THEN ACMX = A ACMN = C ELSE ACMX = C ACMN = A END IF IF( ADF.GT.AB ) THEN RT = ADF*SQRT( ONE+( AB / ADF )**2 ) ELSE IF( ADF.LT.AB ) THEN RT = AB*SQRT( ONE+( ADF / AB )**2 ) ELSE** Includes case AB=ADF=0* RT = AB*SQRT( TWO ) END IF IF( SM.LT.ZERO ) THEN RT1 = HALF*( SM-RT ) SGN1 = -1** Order of execution important.* To get fully accurate smaller eigenvalue,* next line needs to be executed in higher precision.* RT2 = ( ACMX / RT1 )*ACMN - ( B / RT1 )*B ELSE IF( SM.GT.ZERO ) THEN RT1 = HALF*( SM+RT ) SGN1 = 1** Order of execution important.* To get fully accurate smaller eigenvalue,* next line needs to be executed in higher precision.* RT2 = ( ACMX / RT1 )*ACMN - ( B / RT1 )*B ELSE** Includes case RT1 = RT2 = 0* RT1 = HALF*RT RT2 = -HALF*RT SGN1 = 1 END IF** Compute the eigenvector* IF( DF.GE.ZERO ) THEN CS = DF + RT SGN2 = 1 ELSE CS = DF - RT SGN2 = -1 END IF ACS = ABS( CS ) IF( ACS.GT.AB ) THEN CT = -TB / CS SN1 = ONE / SQRT( ONE+CT*CT ) CS1 = CT*SN1 ELSE IF( AB.EQ.ZERO ) THEN CS1 = ONE SN1 = ZERO ELSE TN = -CS / TB CS1 = ONE / SQRT( ONE+TN*TN ) SN1 = TN*CS1 END IF END IF IF( SGN1.EQ.SGN2 ) THEN TN = CS1 CS1 = -SN1 SN1 = TN END IF RETURN** End of DLAEV2* END DOUBLE PRECISION FUNCTION PDLAMCH( CMACH )** -- LAPACK auxiliary routine (version 3.0) --* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,* Courant Institute, Argonne National Lab, and Rice University* October 31, 1992** .. Scalar Arguments .. CHARACTER CMACH* ..** Purpose* =======** DLAMCH determines double precision machine parameters.** Arguments* =========** CMACH (input) CHARACTER*1* Specifies the value to be returned by DLAMCH:* = 'E' or 'e', DLAMCH := eps* = 'S' or 's , DLAMCH := sfmin* = 'B' or 'b', DLAMCH := base* = 'P' or 'p', DLAMCH := eps*base* = 'N' or 'n', DLAMCH := t* = 'R' or 'r', DLAMCH := rnd* = 'M' or 'm', DLAMCH := emin* = 'U' or 'u', DLAMCH := rmin* = 'L' or 'l', DLAMCH := emax* = 'O' or 'o', DLAMCH := rmax** where** eps = relative machine precision* sfmin = safe minimum, such that 1/sfmin does not overflow* base = base of the machine* prec = eps*base* t = number of (base) digits in the mantissa* rnd = 1.0 when rounding occurs in addition, 0.0 otherwise* emin = minimum exponent before (gradual) underflow* rmin = underflow threshold - base**(emin-1)* emax = largest exponent before overflow* rmax = overflow threshold - (base**emax)*(1-eps)** =====================================================================** .. Parameters .. DOUBLE PRECISION ONE, ZERO PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )* ..* .. Local Scalars .. LOGICAL FIRST, LRND INTEGER BETA, IMAX, IMIN, IT DOUBLE PRECISION BASE, EMAX, EMIN, EPS, PREC, RMACH, RMAX, RMIN, $ RND, SFMIN, SMALL, T* ..* .. External Functions .. LOGICAL PLSAME EXTERNAL PLSAME* ..* .. External Subroutines .. EXTERNAL PDLAMC2* ..* .. Save statement .. SAVE FIRST, EPS, SFMIN, BASE, T, RND, EMIN, RMIN, $ EMAX, RMAX, PREC* ..* .. Data statements .. DATA FIRST / .TRUE. /* ..* .. Executable Statements ..* IF( FIRST ) THEN FIRST = .FALSE. CALL PDLAMC2( BETA, IT, LRND, EPS, IMIN, RMIN, IMAX, RMAX ) BASE = BETA T = IT IF( LRND ) THEN RND = ONE EPS = ( BASE**( 1-IT ) ) / 2 ELSE RND = ZERO EPS = BASE**( 1-IT ) END IF PREC = EPS*BASE EMIN = IMIN EMAX = IMAX SFMIN = RMIN SMALL = ONE / RMAX IF( SMALL.GE.SFMIN ) THEN** Use SMALL plus a bit, to avoid the possibility of rounding* causing overflow when computing 1/sfmin.* SFMIN = SMALL*( ONE+EPS ) END IF END IF* IF( PLSAME( CMACH, 'E' ) ) THEN RMACH = EPS ELSE IF( PLSAME( CMACH, 'S' ) ) THEN RMACH = SFMIN ELSE IF( PLSAME( CMACH, 'B' ) ) THEN RMACH = BASE ELSE IF( PLSAME( CMACH, 'P' ) ) THEN RMACH = PREC ELSE IF( PLSAME( CMACH, 'N' ) ) THEN RMACH = T ELSE IF( PLSAME( CMACH, 'R' ) ) THEN RMACH = RND ELSE IF( PLSAME( CMACH, 'M' ) ) THEN RMACH = EMIN ELSE IF( PLSAME( CMACH, 'U' ) ) THEN RMACH = RMIN ELSE IF( PLSAME( CMACH, 'L' ) ) THEN RMACH = EMAX ELSE IF( PLSAME( CMACH, 'O' ) ) THEN RMACH = RMAX END IF* PDLAMCH = RMACH RETURN** End of DLAMCH* END************************************************************************** SUBROUTINE PDLAMC1( BETA, T, RND, IEEE1 )** -- LAPACK auxiliary routine (version 3.0) --* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,* Courant Institute, Argonne National Lab, and Rice University* October 31, 1992** .. Scalar Arguments ..
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -