📄 lapack.f
字号:
* 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 DLANSP( NORM, UPLO, N, AP, WORK )** -- LAPACK auxiliary routine (version 2.0) --* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,* Courant Institute, Argonne National Lab, and Rice University* October 31, 1992** .. Scalar Arguments .. CHARACTER NORM, UPLO INTEGER N* ..* .. Array Arguments .. DOUBLE PRECISION AP( * ), WORK( * )* ..** Purpose* =======** DLANSP returns the value of the one norm, or the Frobenius norm, or* the infinity norm, or the element of largest absolute value of a* real symmetric matrix A, supplied in packed form.** Description* ===========** DLANSP returns the value** DLANSP = ( max(abs(A(i,j))), NORM = 'M' or 'm'* (* ( norm1(A), NORM = '1', 'O' or 'o'* (* ( normI(A), NORM = 'I' or 'i'* (* ( normF(A), NORM = 'F', 'f', 'E' or 'e'** where norm1 denotes the one norm of a matrix (maximum column sum),* normI denotes the infinity norm of a matrix (maximum row sum) and* normF denotes the Frobenius norm of a matrix (square root of sum of* squares). Note that max(abs(A(i,j))) is not a matrix norm.** Arguments* =========** NORM (input) CHARACTER*1* Specifies the value to be returned in DLANSP as described* above.** UPLO (input) CHARACTER*1* Specifies whether the upper or lower triangular part of the* symmetric matrix A is supplied.* = 'U': Upper triangular part of A is supplied* = 'L': Lower triangular part of A is supplied** N (input) INTEGER* The order of the matrix A. N >= 0. When N = 0, DLANSP is* set to zero.** AP (input) DOUBLE PRECISION array, dimension (N*(N+1)/2)* The upper or lower triangle of the symmetric matrix A, packed* columnwise in a linear array. The j-th column of A is stored* in the array AP as follows:* if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;* if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.** WORK (workspace) DOUBLE PRECISION array, dimension (LWORK),* where LWORK >= N when NORM = 'I' or '1' or 'O'; otherwise,* WORK is not referenced.** =====================================================================** .. Parameters .. DOUBLE PRECISION ONE, ZERO PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )* ..* .. Local Scalars .. INTEGER I, J, K DOUBLE PRECISION ABSA, SCALE, SUM, VALUE* ..* .. External Subroutines .. EXTERNAL DLASSQ* ..* .. External Functions .. LOGICAL LSAME EXTERNAL LSAME* ..* .. Intrinsic Functions .. INTRINSIC ABS, MAX, SQRT* ..* .. Executable Statements ..* IF( N.EQ.0 ) THEN VALUE = ZERO ELSE IF( LSAME( NORM, 'M' ) ) THEN** Find max(abs(A(i,j))).* VALUE = ZERO IF( LSAME( UPLO, 'U' ) ) THEN K = 1 DO 20 J = 1, N DO 10 I = K, K + J - 1 VALUE = MAX( VALUE, ABS( AP( I ) ) ) 10 CONTINUE K = K + J 20 CONTINUE ELSE K = 1 DO 40 J = 1, N DO 30 I = K, K + N - J VALUE = MAX( VALUE, ABS( AP( I ) ) ) 30 CONTINUE K = K + N - J + 1 40 CONTINUE END IF ELSE IF( ( LSAME( NORM, 'I' ) ) .OR. ( LSAME( NORM, 'O' ) ) .OR. $ ( NORM.EQ.'1' ) ) THEN** Find normI(A) ( = norm1(A), since A is symmetric).* VALUE = ZERO K = 1 IF( LSAME( UPLO, 'U' ) ) THEN DO 60 J = 1, N SUM = ZERO DO 50 I = 1, J - 1 ABSA = ABS( AP( K ) ) SUM = SUM + ABSA WORK( I ) = WORK( I ) + ABSA K = K + 1 50 CONTINUE WORK( J ) = SUM + ABS( AP( K ) ) K = K + 1 60 CONTINUE DO 70 I = 1, N VALUE = MAX( VALUE, WORK( I ) ) 70 CONTINUE ELSE DO 80 I = 1, N WORK( I ) = ZERO 80 CONTINUE DO 100 J = 1, N SUM = WORK( J ) + ABS( AP( K ) ) K = K + 1 DO 90 I = J + 1, N ABSA = ABS( AP( K ) ) SUM = SUM + ABSA WORK( I ) = WORK( I ) + ABSA K = K + 1 90 CONTINUE VALUE = MAX( VALUE, SUM ) 100 CONTINUE END IF ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN** Find normF(A).* SCALE = ZERO SUM = ONE K = 2 IF( LSAME( UPLO, 'U' ) ) THEN DO 110 J = 2, N CALL DLASSQ( J-1, AP( K ), 1, SCALE, SUM ) K = K + J 110 CONTINUE ELSE DO 120 J = 1, N - 1 CALL DLASSQ( N-J, AP( K ), 1, SCALE, SUM ) K = K + N - J + 1 120 CONTINUE END IF SUM = 2*SUM K = 1 DO 130 I = 1, N IF( AP( K ).NE.ZERO ) THEN ABSA = ABS( AP( K ) ) IF( SCALE.LT.ABSA ) THEN SUM = ONE + SUM*( SCALE / ABSA )**2 SCALE = ABSA ELSE SUM = SUM + ( ABSA / SCALE )**2 END IF END IF IF( LSAME( UPLO, 'U' ) ) THEN K = K + I + 1 ELSE K = K + N - I + 1 END IF 130 CONTINUE VALUE = SCALE*SQRT( SUM ) END IF* DLANSP = VALUE RETURN** End of DLANSP* END DOUBLE PRECISION FUNCTION DLANST( NORM, N, D, E )** -- LAPACK auxiliary routine (version 2.0) --* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,* Courant Institute, Argonne National Lab, and Rice University* February 29, 1992** .. Scalar Arguments .. CHARACTER NORM INTEGER N* ..* .. Array Arguments .. DOUBLE PRECISION D( * ), E( * )* ..** Purpose* =======** DLANST returns the value of the one norm, or the Frobenius norm, or* the infinity norm, or the element of largest absolute value of a* real symmetric tridiagonal matrix A.** Description* ===========** DLANST returns the value** DLANST = ( max(abs(A(i,j))), NORM = 'M' or 'm'* (* ( norm1(A), NORM = '1', 'O' or 'o'* (* ( normI(A), NORM = 'I' or 'i'* (* ( normF(A), NORM = 'F', 'f', 'E' or 'e'** where norm1 denotes the one norm of a matrix (maximum column sum),* normI denotes the infinity norm of a matrix (maximum row sum) and* normF denotes the Frobenius norm of a matrix (square root of sum of* squares). Note that max(abs(A(i,j))) is not a matrix norm.** Arguments* =========** NORM (input) CHARACTER*1* Specifies the value to be returned in DLANST as described* above.** N (input) INTEGER* The order of the matrix A. N >= 0. When N = 0, DLANST is* set to zero.** D (input) DOUBLE PRECISION array, dimension (N)* The diagonal elements of A.** E (input) DOUBLE PRECISION array, dimension (N-1)* The (n-1) sub-diagonal or super-diagonal elements of A.** =====================================================================** .. Parameters .. DOUBLE PRECISION ONE, ZERO PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )* ..* .. Local Scalars .. INTEGER I DOUBLE PRECISION ANORM, SCALE, SUM* ..* .. External Functions .. LOGICAL LSAME EXTERNAL LSAME* ..* .. External Subroutines .. EXTERNAL DLASSQ* ..* .. Intrinsic Functions .. INTRINSIC ABS, MAX, SQRT* ..* .. Executable Statements ..* IF( N.LE.0 ) THEN ANORM = ZERO ELSE IF( LSAME( NORM, 'M' ) ) THEN** Find max(abs(A(i,j))).* ANORM = ABS( D( N ) ) DO 10 I = 1, N - 1 ANORM = MAX( ANORM, ABS( D( I ) ) ) ANORM = MAX( ANORM, ABS( E( I ) ) ) 10 CONTINUE ELSE IF( LSAME( NORM, 'O' ) .OR. NORM.EQ.'1' .OR. $ LSAME( NORM, 'I' ) ) THEN** Find norm1(A).* IF( N.EQ.1 ) THEN ANORM = ABS( D( 1 ) ) ELSE ANORM = MAX( ABS( D( 1 ) )+ABS( E( 1 ) ), $ ABS( E( N-1 ) )+ABS( D( N ) ) ) DO 20 I = 2, N - 1 ANORM = MAX( ANORM, ABS( D( I ) )+ABS( E( I ) )+ $ ABS( E( I-1 ) ) ) 20 CONTINUE END IF ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN** Find normF(A).* SCALE = ZERO SUM = ONE IF( N.GT.1 ) THEN CALL DLASSQ( N-1, E, 1, SCALE, SUM ) SUM = 2*SUM END IF CALL DLASSQ( N, D, 1, SCALE, SUM ) ANORM = SCALE*SQRT( SUM ) END IF* DLANST = ANORM RETURN** End of DLANST* END DOUBLE PRECISION FUNCTION DLAPY2( X, Y )** -- LAPACK auxiliary routine (version 2.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 X, Y* ..** Purpose* =======** DLAPY2 returns sqrt(x**2+y**2), taking care not to cause unnecessary* overflow.** Arguments* =========** X (input) DOUBLE PRECISION* Y (input) DOUBLE PRECISION* X and Y specify the values x and y.** =====================================================================** .. Parameters .. DOUBLE PRECISION ZERO PARAMETER ( ZERO = 0.0D0 ) DOUBLE PRECISION ONE PARAMETER ( ONE = 1.0D0 )* ..* .. Local Scalars .. DOUBLE PRECISION W, XABS, YABS, Z* ..* .. Intrinsic Functions .. INTRINSIC ABS, MAX, MIN, SQRT* ..* .. Executable Statements ..* XABS = ABS( X ) YABS = ABS( Y ) W = MAX( XABS, YABS ) Z = MIN( XABS, YABS ) IF( Z.EQ.ZERO ) THEN DLAPY2 = W ELSE DLAPY2 = W*SQRT( ONE+( Z / W )**2 ) END IF RETURN** End of DLAPY2* END SUBROUTINE DLARF( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )** -- LAPACK auxiliary routine (version 2.0) --* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,* Courant Institute, Argonne National Lab, and Rice University* February 29, 1992** .. Scalar Arguments .. CHARACTER SIDE INTEGER INCV, LDC, M, N DOUBLE PRECISION TAU* ..* .. Array Arguments .. DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )* ..** Purpose* =======** DLARF applies a real elementary reflector H to a real m by n matrix* C, from either the left or the right. H is represented in the form** H = I - tau * v * v'** where tau is a real scalar and v is a real vector.** If tau = 0, then H is taken to be the unit matrix.** Arguments* =========
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -