1*> \brief \b DSPCON
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download DSPCON + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dspcon.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dspcon.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dspcon.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE DSPCON( UPLO, N, AP, IPIV, ANORM, RCOND, WORK, IWORK,
22*                          INFO )
23*
24*       .. Scalar Arguments ..
25*       CHARACTER          UPLO
26*       INTEGER            INFO, N
27*       DOUBLE PRECISION   ANORM, RCOND
28*       ..
29*       .. Array Arguments ..
30*       INTEGER            IPIV( * ), IWORK( * )
31*       DOUBLE PRECISION   AP( * ), WORK( * )
32*       ..
33*
34*
35*> \par Purpose:
36*  =============
37*>
38*> \verbatim
39*>
40*> DSPCON estimates the reciprocal of the condition number (in the
41*> 1-norm) of a real symmetric packed matrix A using the factorization
42*> A = U*D*U**T or A = L*D*L**T computed by DSPTRF.
43*>
44*> An estimate is obtained for norm(inv(A)), and the reciprocal of the
45*> condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
46*> \endverbatim
47*
48*  Arguments:
49*  ==========
50*
51*> \param[in] UPLO
52*> \verbatim
53*>          UPLO is CHARACTER*1
54*>          Specifies whether the details of the factorization are stored
55*>          as an upper or lower triangular matrix.
56*>          = 'U':  Upper triangular, form is A = U*D*U**T;
57*>          = 'L':  Lower triangular, form is A = L*D*L**T.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*>          N is INTEGER
63*>          The order of the matrix A.  N >= 0.
64*> \endverbatim
65*>
66*> \param[in] AP
67*> \verbatim
68*>          AP is DOUBLE PRECISION array, dimension (N*(N+1)/2)
69*>          The block diagonal matrix D and the multipliers used to
70*>          obtain the factor U or L as computed by DSPTRF, stored as a
71*>          packed triangular matrix.
72*> \endverbatim
73*>
74*> \param[in] IPIV
75*> \verbatim
76*>          IPIV is INTEGER array, dimension (N)
77*>          Details of the interchanges and the block structure of D
78*>          as determined by DSPTRF.
79*> \endverbatim
80*>
81*> \param[in] ANORM
82*> \verbatim
83*>          ANORM is DOUBLE PRECISION
84*>          The 1-norm of the original matrix A.
85*> \endverbatim
86*>
87*> \param[out] RCOND
88*> \verbatim
89*>          RCOND is DOUBLE PRECISION
90*>          The reciprocal of the condition number of the matrix A,
91*>          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
92*>          estimate of the 1-norm of inv(A) computed in this routine.
93*> \endverbatim
94*>
95*> \param[out] WORK
96*> \verbatim
97*>          WORK is DOUBLE PRECISION array, dimension (2*N)
98*> \endverbatim
99*>
100*> \param[out] IWORK
101*> \verbatim
102*>          IWORK is INTEGER array, dimension (N)
103*> \endverbatim
104*>
105*> \param[out] INFO
106*> \verbatim
107*>          INFO is INTEGER
108*>          = 0:  successful exit
109*>          < 0:  if INFO = -i, the i-th argument had an illegal value
110*> \endverbatim
111*
112*  Authors:
113*  ========
114*
115*> \author Univ. of Tennessee
116*> \author Univ. of California Berkeley
117*> \author Univ. of Colorado Denver
118*> \author NAG Ltd.
119*
120*> \date December 2016
121*
122*> \ingroup doubleOTHERcomputational
123*
124*  =====================================================================
125      SUBROUTINE DSPCON( UPLO, N, AP, IPIV, ANORM, RCOND, WORK, IWORK,
126     $                   INFO )
127*
128*  -- LAPACK computational routine (version 3.7.0) --
129*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
130*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131*     December 2016
132*
133*     .. Scalar Arguments ..
134      CHARACTER          UPLO
135      INTEGER            INFO, N
136      DOUBLE PRECISION   ANORM, RCOND
137*     ..
138*     .. Array Arguments ..
139      INTEGER            IPIV( * ), IWORK( * )
140      DOUBLE PRECISION   AP( * ), WORK( * )
141*     ..
142*
143*  =====================================================================
144*
145*     .. Parameters ..
146      DOUBLE PRECISION   ONE, ZERO
147      PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
148*     ..
149*     .. Local Scalars ..
150      LOGICAL            UPPER
151      INTEGER            I, IP, KASE
152      DOUBLE PRECISION   AINVNM
153*     ..
154*     .. Local Arrays ..
155      INTEGER            ISAVE( 3 )
156*     ..
157*     .. External Functions ..
158      LOGICAL            LSAME
159      EXTERNAL           LSAME
160*     ..
161*     .. External Subroutines ..
162      EXTERNAL           DLACN2, DSPTRS, XERBLA
163*     ..
164*     .. Executable Statements ..
165*
166*     Test the input parameters.
167*
168      INFO = 0
169      UPPER = LSAME( UPLO, 'U' )
170      IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
171         INFO = -1
172      ELSE IF( N.LT.0 ) THEN
173         INFO = -2
174      ELSE IF( ANORM.LT.ZERO ) THEN
175         INFO = -5
176      END IF
177      IF( INFO.NE.0 ) THEN
178         CALL XERBLA( 'DSPCON', -INFO )
179         RETURN
180      END IF
181*
182*     Quick return if possible
183*
184      RCOND = ZERO
185      IF( N.EQ.0 ) THEN
186         RCOND = ONE
187         RETURN
188      ELSE IF( ANORM.LE.ZERO ) THEN
189         RETURN
190      END IF
191*
192*     Check that the diagonal matrix D is nonsingular.
193*
194      IF( UPPER ) THEN
195*
196*        Upper triangular storage: examine D from bottom to top
197*
198         IP = N*( N+1 ) / 2
199         DO 10 I = N, 1, -1
200            IF( IPIV( I ).GT.0 .AND. AP( IP ).EQ.ZERO )
201     $         RETURN
202            IP = IP - I
203   10    CONTINUE
204      ELSE
205*
206*        Lower triangular storage: examine D from top to bottom.
207*
208         IP = 1
209         DO 20 I = 1, N
210            IF( IPIV( I ).GT.0 .AND. AP( IP ).EQ.ZERO )
211     $         RETURN
212            IP = IP + N - I + 1
213   20    CONTINUE
214      END IF
215*
216*     Estimate the 1-norm of the inverse.
217*
218      KASE = 0
219   30 CONTINUE
220      CALL DLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
221      IF( KASE.NE.0 ) THEN
222*
223*        Multiply by inv(L*D*L**T) or inv(U*D*U**T).
224*
225         CALL DSPTRS( UPLO, N, 1, AP, IPIV, WORK, N, INFO )
226         GO TO 30
227      END IF
228*
229*     Compute the estimate of the reciprocal condition number.
230*
231      IF( AINVNM.NE.ZERO )
232     $   RCOND = ( ONE / AINVNM ) / ANORM
233*
234      RETURN
235*
236*     End of DSPCON
237*
238      END
239