LAPACK 3.3.0

ssycon.f

Go to the documentation of this file.
00001       SUBROUTINE SSYCON( UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK,
00002      $                   IWORK, INFO )
00003 *
00004 *  -- LAPACK routine (version 3.2) --
00005 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00006 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00007 *     November 2006
00008 *
00009 *     Modified to call SLACN2 in place of SLACON, 7 Feb 03, SJH.
00010 *
00011 *     .. Scalar Arguments ..
00012       CHARACTER          UPLO
00013       INTEGER            INFO, LDA, N
00014       REAL               ANORM, RCOND
00015 *     ..
00016 *     .. Array Arguments ..
00017       INTEGER            IPIV( * ), IWORK( * )
00018       REAL               A( LDA, * ), WORK( * )
00019 *     ..
00020 *
00021 *  Purpose
00022 *  =======
00023 *
00024 *  SSYCON estimates the reciprocal of the condition number (in the
00025 *  1-norm) of a real symmetric matrix A using the factorization
00026 *  A = U*D*U**T or A = L*D*L**T computed by SSYTRF.
00027 *
00028 *  An estimate is obtained for norm(inv(A)), and the reciprocal of the
00029 *  condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
00030 *
00031 *  Arguments
00032 *  =========
00033 *
00034 *  UPLO    (input) CHARACTER*1
00035 *          Specifies whether the details of the factorization are stored
00036 *          as an upper or lower triangular matrix.
00037 *          = 'U':  Upper triangular, form is A = U*D*U**T;
00038 *          = 'L':  Lower triangular, form is A = L*D*L**T.
00039 *
00040 *  N       (input) INTEGER
00041 *          The order of the matrix A.  N >= 0.
00042 *
00043 *  A       (input) REAL array, dimension (LDA,N)
00044 *          The block diagonal matrix D and the multipliers used to
00045 *          obtain the factor U or L as computed by SSYTRF.
00046 *
00047 *  LDA     (input) INTEGER
00048 *          The leading dimension of the array A.  LDA >= max(1,N).
00049 *
00050 *  IPIV    (input) INTEGER array, dimension (N)
00051 *          Details of the interchanges and the block structure of D
00052 *          as determined by SSYTRF.
00053 *
00054 *  ANORM   (input) REAL
00055 *          The 1-norm of the original matrix A.
00056 *
00057 *  RCOND   (output) REAL
00058 *          The reciprocal of the condition number of the matrix A,
00059 *          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
00060 *          estimate of the 1-norm of inv(A) computed in this routine.
00061 *
00062 *  WORK    (workspace) REAL array, dimension (2*N)
00063 *
00064 *  IWORK    (workspace) INTEGER array, dimension (N)
00065 *
00066 *  INFO    (output) INTEGER
00067 *          = 0:  successful exit
00068 *          < 0:  if INFO = -i, the i-th argument had an illegal value
00069 *
00070 *  =====================================================================
00071 *
00072 *     .. Parameters ..
00073       REAL               ONE, ZERO
00074       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
00075 *     ..
00076 *     .. Local Scalars ..
00077       LOGICAL            UPPER
00078       INTEGER            I, KASE
00079       REAL               AINVNM
00080 *     ..
00081 *     .. Local Arrays ..
00082       INTEGER            ISAVE( 3 )
00083 *     ..
00084 *     .. External Functions ..
00085       LOGICAL            LSAME
00086       EXTERNAL           LSAME
00087 *     ..
00088 *     .. External Subroutines ..
00089       EXTERNAL           SLACN2, SSYTRS, XERBLA
00090 *     ..
00091 *     .. Intrinsic Functions ..
00092       INTRINSIC          MAX
00093 *     ..
00094 *     .. Executable Statements ..
00095 *
00096 *     Test the input parameters.
00097 *
00098       INFO = 0
00099       UPPER = LSAME( UPLO, 'U' )
00100       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
00101          INFO = -1
00102       ELSE IF( N.LT.0 ) THEN
00103          INFO = -2
00104       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
00105          INFO = -4
00106       ELSE IF( ANORM.LT.ZERO ) THEN
00107          INFO = -6
00108       END IF
00109       IF( INFO.NE.0 ) THEN
00110          CALL XERBLA( 'SSYCON', -INFO )
00111          RETURN
00112       END IF
00113 *
00114 *     Quick return if possible
00115 *
00116       RCOND = ZERO
00117       IF( N.EQ.0 ) THEN
00118          RCOND = ONE
00119          RETURN
00120       ELSE IF( ANORM.LE.ZERO ) THEN
00121          RETURN
00122       END IF
00123 *
00124 *     Check that the diagonal matrix D is nonsingular.
00125 *
00126       IF( UPPER ) THEN
00127 *
00128 *        Upper triangular storage: examine D from bottom to top
00129 *
00130          DO 10 I = N, 1, -1
00131             IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.ZERO )
00132      $         RETURN
00133    10    CONTINUE
00134       ELSE
00135 *
00136 *        Lower triangular storage: examine D from top to bottom.
00137 *
00138          DO 20 I = 1, N
00139             IF( IPIV( I ).GT.0 .AND. A( I, I ).EQ.ZERO )
00140      $         RETURN
00141    20    CONTINUE
00142       END IF
00143 *
00144 *     Estimate the 1-norm of the inverse.
00145 *
00146       KASE = 0
00147    30 CONTINUE
00148       CALL SLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
00149       IF( KASE.NE.0 ) THEN
00150 *
00151 *        Multiply by inv(L*D*L') or inv(U*D*U').
00152 *
00153          CALL SSYTRS( UPLO, N, 1, A, LDA, IPIV, WORK, N, INFO )
00154          GO TO 30
00155       END IF
00156 *
00157 *     Compute the estimate of the reciprocal condition number.
00158 *
00159       IF( AINVNM.NE.ZERO )
00160      $   RCOND = ( ONE / AINVNM ) / ANORM
00161 *
00162       RETURN
00163 *
00164 *     End of SSYCON
00165 *
00166       END
 All Files Functions