LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ctptri.f
Go to the documentation of this file.
1 *> \brief \b CTPTRI
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CTPTRI + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ctptri.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ctptri.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ctptri.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CTPTRI( UPLO, DIAG, N, AP, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER DIAG, UPLO
25 * INTEGER INFO, N
26 * ..
27 * .. Array Arguments ..
28 * COMPLEX AP( * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> CTPTRI computes the inverse of a complex upper or lower triangular
38 *> matrix A stored in packed format.
39 *> \endverbatim
40 *
41 * Arguments:
42 * ==========
43 *
44 *> \param[in] UPLO
45 *> \verbatim
46 *> UPLO is CHARACTER*1
47 *> = 'U': A is upper triangular;
48 *> = 'L': A is lower triangular.
49 *> \endverbatim
50 *>
51 *> \param[in] DIAG
52 *> \verbatim
53 *> DIAG is CHARACTER*1
54 *> = 'N': A is non-unit triangular;
55 *> = 'U': A is unit triangular.
56 *> \endverbatim
57 *>
58 *> \param[in] N
59 *> \verbatim
60 *> N is INTEGER
61 *> The order of the matrix A. N >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in,out] AP
65 *> \verbatim
66 *> AP is COMPLEX array, dimension (N*(N+1)/2)
67 *> On entry, the upper or lower triangular matrix A, stored
68 *> columnwise in a linear array. The j-th column of A is stored
69 *> in the array AP as follows:
70 *> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
71 *> if UPLO = 'L', AP(i + (j-1)*((2*n-j)/2) = A(i,j) for j<=i<=n.
72 *> See below for further details.
73 *> On exit, the (triangular) inverse of the original matrix, in
74 *> the same packed storage format.
75 *> \endverbatim
76 *>
77 *> \param[out] INFO
78 *> \verbatim
79 *> INFO is INTEGER
80 *> = 0: successful exit
81 *> < 0: if INFO = -i, the i-th argument had an illegal value
82 *> > 0: if INFO = i, A(i,i) is exactly zero. The triangular
83 *> matrix is singular and its inverse can not be computed.
84 *> \endverbatim
85 *
86 * Authors:
87 * ========
88 *
89 *> \author Univ. of Tennessee
90 *> \author Univ. of California Berkeley
91 *> \author Univ. of Colorado Denver
92 *> \author NAG Ltd.
93 *
94 *> \date November 2011
95 *
96 *> \ingroup complexOTHERcomputational
97 *
98 *> \par Further Details:
99 * =====================
100 *>
101 *> \verbatim
102 *>
103 *> A triangular matrix A can be transferred to packed storage using one
104 *> of the following program segments:
105 *>
106 *> UPLO = 'U': UPLO = 'L':
107 *>
108 *> JC = 1 JC = 1
109 *> DO 2 J = 1, N DO 2 J = 1, N
110 *> DO 1 I = 1, J DO 1 I = J, N
111 *> AP(JC+I-1) = A(I,J) AP(JC+I-J) = A(I,J)
112 *> 1 CONTINUE 1 CONTINUE
113 *> JC = JC + J JC = JC + N - J + 1
114 *> 2 CONTINUE 2 CONTINUE
115 *> \endverbatim
116 *>
117 * =====================================================================
118  SUBROUTINE ctptri( UPLO, DIAG, N, AP, INFO )
119 *
120 * -- LAPACK computational routine (version 3.4.0) --
121 * -- LAPACK is a software package provided by Univ. of Tennessee, --
122 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123 * November 2011
124 *
125 * .. Scalar Arguments ..
126  CHARACTER diag, uplo
127  INTEGER info, n
128 * ..
129 * .. Array Arguments ..
130  COMPLEX ap( * )
131 * ..
132 *
133 * =====================================================================
134 *
135 * .. Parameters ..
136  COMPLEX one, zero
137  parameter( one = ( 1.0e+0, 0.0e+0 ),
138  $ zero = ( 0.0e+0, 0.0e+0 ) )
139 * ..
140 * .. Local Scalars ..
141  LOGICAL nounit, upper
142  INTEGER j, jc, jclast, jj
143  COMPLEX ajj
144 * ..
145 * .. External Functions ..
146  LOGICAL lsame
147  EXTERNAL lsame
148 * ..
149 * .. External Subroutines ..
150  EXTERNAL cscal, ctpmv, xerbla
151 * ..
152 * .. Executable Statements ..
153 *
154 * Test the input parameters.
155 *
156  info = 0
157  upper = lsame( uplo, 'U' )
158  nounit = lsame( diag, 'N' )
159  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
160  info = -1
161  ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
162  info = -2
163  ELSE IF( n.LT.0 ) THEN
164  info = -3
165  END IF
166  IF( info.NE.0 ) THEN
167  CALL xerbla( 'CTPTRI', -info )
168  return
169  END IF
170 *
171 * Check for singularity if non-unit.
172 *
173  IF( nounit ) THEN
174  IF( upper ) THEN
175  jj = 0
176  DO 10 info = 1, n
177  jj = jj + info
178  IF( ap( jj ).EQ.zero )
179  $ return
180  10 continue
181  ELSE
182  jj = 1
183  DO 20 info = 1, n
184  IF( ap( jj ).EQ.zero )
185  $ return
186  jj = jj + n - info + 1
187  20 continue
188  END IF
189  info = 0
190  END IF
191 *
192  IF( upper ) THEN
193 *
194 * Compute inverse of upper triangular matrix.
195 *
196  jc = 1
197  DO 30 j = 1, n
198  IF( nounit ) THEN
199  ap( jc+j-1 ) = one / ap( jc+j-1 )
200  ajj = -ap( jc+j-1 )
201  ELSE
202  ajj = -one
203  END IF
204 *
205 * Compute elements 1:j-1 of j-th column.
206 *
207  CALL ctpmv( 'Upper', 'No transpose', diag, j-1, ap,
208  $ ap( jc ), 1 )
209  CALL cscal( j-1, ajj, ap( jc ), 1 )
210  jc = jc + j
211  30 continue
212 *
213  ELSE
214 *
215 * Compute inverse of lower triangular matrix.
216 *
217  jc = n*( n+1 ) / 2
218  DO 40 j = n, 1, -1
219  IF( nounit ) THEN
220  ap( jc ) = one / ap( jc )
221  ajj = -ap( jc )
222  ELSE
223  ajj = -one
224  END IF
225  IF( j.LT.n ) THEN
226 *
227 * Compute elements j+1:n of j-th column.
228 *
229  CALL ctpmv( 'Lower', 'No transpose', diag, n-j,
230  $ ap( jclast ), ap( jc+1 ), 1 )
231  CALL cscal( n-j, ajj, ap( jc+1 ), 1 )
232  END IF
233  jclast = jc
234  jc = jc - n + j - 2
235  40 continue
236  END IF
237 *
238  return
239 *
240 * End of CTPTRI
241 *
242  END