STYLE: Remove trailing whitespace in Fortran files
[platform/upstream/lapack.git] / SRC / zsytri2.f
1 *> \brief \b ZSYTRI2
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZSYTRI2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zsytri2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zsytri2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytri2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZSYTRI2( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
22 *
23 *       .. Scalar Arguments ..
24 *       CHARACTER          UPLO
25 *       INTEGER            INFO, LDA, LWORK, N
26 *       ..
27 *       .. Array Arguments ..
28 *       INTEGER            IPIV( * )
29 *       COMPLEX*16         A( LDA, * ), WORK( * )
30 *       ..
31 *
32 *
33 *> \par Purpose:
34 *  =============
35 *>
36 *> \verbatim
37 *>
38 *> ZSYTRI2 computes the inverse of a COMPLEX*16 symmetric indefinite matrix
39 *> A using the factorization A = U*D*U**T or A = L*D*L**T computed by
40 *> ZSYTRF. ZSYTRI2 sets the LEADING DIMENSION of the workspace
41 *> before calling ZSYTRI2X that actually computes the inverse.
42 *> \endverbatim
43 *
44 *  Arguments:
45 *  ==========
46 *
47 *> \param[in] UPLO
48 *> \verbatim
49 *>          UPLO is CHARACTER*1
50 *>          Specifies whether the details of the factorization are stored
51 *>          as an upper or lower triangular matrix.
52 *>          = 'U':  Upper triangular, form is A = U*D*U**T;
53 *>          = 'L':  Lower triangular, form is A = L*D*L**T.
54 *> \endverbatim
55 *>
56 *> \param[in] N
57 *> \verbatim
58 *>          N is INTEGER
59 *>          The order of the matrix A.  N >= 0.
60 *> \endverbatim
61 *>
62 *> \param[in,out] A
63 *> \verbatim
64 *>          A is COMPLEX*16 array, dimension (LDA,N)
65 *>          On entry, the NB diagonal matrix D and the multipliers
66 *>          used to obtain the factor U or L as computed by ZSYTRF.
67 *>
68 *>          On exit, if INFO = 0, the (symmetric) inverse of the original
69 *>          matrix.  If UPLO = 'U', the upper triangular part of the
70 *>          inverse is formed and the part of A below the diagonal is not
71 *>          referenced; if UPLO = 'L' the lower triangular part of the
72 *>          inverse is formed and the part of A above the diagonal is
73 *>          not referenced.
74 *> \endverbatim
75 *>
76 *> \param[in] LDA
77 *> \verbatim
78 *>          LDA is INTEGER
79 *>          The leading dimension of the array A.  LDA >= max(1,N).
80 *> \endverbatim
81 *>
82 *> \param[in] IPIV
83 *> \verbatim
84 *>          IPIV is INTEGER array, dimension (N)
85 *>          Details of the interchanges and the NB structure of D
86 *>          as determined by ZSYTRF.
87 *> \endverbatim
88 *>
89 *> \param[out] WORK
90 *> \verbatim
91 *>          WORK is COMPLEX*16 array, dimension (N+NB+1)*(NB+3)
92 *> \endverbatim
93 *>
94 *> \param[in] LWORK
95 *> \verbatim
96 *>          LWORK is INTEGER
97 *>          The dimension of the array WORK.
98 *>          WORK is size >= (N+NB+1)*(NB+3)
99 *>          If LDWORK = -1, then a workspace query is assumed; the routine
100 *>           calculates:
101 *>              - the optimal size of the WORK array, returns
102 *>          this value as the first entry of the WORK array,
103 *>              - and no error message related to LDWORK is issued by XERBLA.
104 *> \endverbatim
105 *>
106 *> \param[out] INFO
107 *> \verbatim
108 *>          INFO is INTEGER
109 *>          = 0: successful exit
110 *>          < 0: if INFO = -i, the i-th argument had an illegal value
111 *>          > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
112 *>               inverse could not be computed.
113 *> \endverbatim
114 *
115 *  Authors:
116 *  ========
117 *
118 *> \author Univ. of Tennessee
119 *> \author Univ. of California Berkeley
120 *> \author Univ. of Colorado Denver
121 *> \author NAG Ltd.
122 *
123 *> \date November 2015
124 *
125 *> \ingroup complex16SYcomputational
126 *
127 *  =====================================================================
128       SUBROUTINE ZSYTRI2( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
129 *
130 *  -- LAPACK computational routine (version 3.6.0) --
131 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
132 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
133 *     November 2015
134 *
135 *     .. Scalar Arguments ..
136       CHARACTER          UPLO
137       INTEGER            INFO, LDA, LWORK, N
138 *     ..
139 *     .. Array Arguments ..
140       INTEGER            IPIV( * )
141       COMPLEX*16         A( LDA, * ), WORK( * )
142 *     ..
143 *
144 *  =====================================================================
145 *
146 *     .. Local Scalars ..
147       LOGICAL            UPPER, LQUERY
148       INTEGER            MINSIZE, NBMAX
149 *     ..
150 *     .. External Functions ..
151       LOGICAL            LSAME
152       INTEGER            ILAENV
153       EXTERNAL           LSAME, ILAENV
154 *     ..
155 *     .. External Subroutines ..
156       EXTERNAL           ZSYTRI, ZSYTRI2X
157 *     ..
158 *     .. Executable Statements ..
159 *
160 *     Test the input parameters.
161 *
162       INFO = 0
163       UPPER = LSAME( UPLO, 'U' )
164       LQUERY = ( LWORK.EQ.-1 )
165 *     Get blocksize
166       NBMAX = ILAENV( 1, 'ZSYTRF', UPLO, N, -1, -1, -1 )
167       IF ( NBMAX .GE. N ) THEN
168          MINSIZE = N
169       ELSE
170          MINSIZE = (N+NBMAX+1)*(NBMAX+3)
171       END IF
172 *
173       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
174          INFO = -1
175       ELSE IF( N.LT.0 ) THEN
176          INFO = -2
177       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
178          INFO = -4
179       ELSE IF (LWORK .LT. MINSIZE .AND. .NOT.LQUERY ) THEN
180          INFO = -7
181       END IF
182 *
183 *     Quick return if possible
184 *
185 *
186       IF( INFO.NE.0 ) THEN
187          CALL XERBLA( 'ZSYTRI2', -INFO )
188          RETURN
189       ELSE IF( LQUERY ) THEN
190          WORK(1)=MINSIZE
191          RETURN
192       END IF
193       IF( N.EQ.0 )
194      $   RETURN
195
196       IF( NBMAX .GE. N ) THEN
197          CALL ZSYTRI( UPLO, N, A, LDA, IPIV, WORK, INFO )
198       ELSE
199          CALL ZSYTRI2X( UPLO, N, A, LDA, IPIV, WORK, NBMAX, INFO )
200       END IF
201       RETURN
202 *
203 *     End of ZSYTRI2
204 *
205       END