LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ztpsv.f
Go to the documentation of this file.
1*> \brief \b ZTPSV
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE ZTPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
12*
13* .. Scalar Arguments ..
14* INTEGER INCX,N
15* CHARACTER DIAG,TRANS,UPLO
16* ..
17* .. Array Arguments ..
18* COMPLEX*16 AP(*),X(*)
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> ZTPSV solves one of the systems of equations
28*>
29*> A*x = b, or A**T*x = b, or A**H*x = b,
30*>
31*> where b and x are n element vectors and A is an n by n unit, or
32*> non-unit, upper or lower triangular matrix, supplied in packed form.
33*>
34*> No test for singularity or near-singularity is included in this
35*> routine. Such tests must be performed before calling this routine.
36*> \endverbatim
37*
38* Arguments:
39* ==========
40*
41*> \param[in] UPLO
42*> \verbatim
43*> UPLO is CHARACTER*1
44*> On entry, UPLO specifies whether the matrix is an upper or
45*> lower triangular matrix as follows:
46*>
47*> UPLO = 'U' or 'u' A is an upper triangular matrix.
48*>
49*> UPLO = 'L' or 'l' A is a lower triangular matrix.
50*> \endverbatim
51*>
52*> \param[in] TRANS
53*> \verbatim
54*> TRANS is CHARACTER*1
55*> On entry, TRANS specifies the equations to be solved as
56*> follows:
57*>
58*> TRANS = 'N' or 'n' A*x = b.
59*>
60*> TRANS = 'T' or 't' A**T*x = b.
61*>
62*> TRANS = 'C' or 'c' A**H*x = b.
63*> \endverbatim
64*>
65*> \param[in] DIAG
66*> \verbatim
67*> DIAG is CHARACTER*1
68*> On entry, DIAG specifies whether or not A is unit
69*> triangular as follows:
70*>
71*> DIAG = 'U' or 'u' A is assumed to be unit triangular.
72*>
73*> DIAG = 'N' or 'n' A is not assumed to be unit
74*> triangular.
75*> \endverbatim
76*>
77*> \param[in] N
78*> \verbatim
79*> N is INTEGER
80*> On entry, N specifies the order of the matrix A.
81*> N must be at least zero.
82*> \endverbatim
83*>
84*> \param[in] AP
85*> \verbatim
86*> AP is COMPLEX*16 array, dimension at least
87*> ( ( n*( n + 1 ) )/2 ).
88*> Before entry with UPLO = 'U' or 'u', the array AP must
89*> contain the upper triangular matrix packed sequentially,
90*> column by column, so that AP( 1 ) contains a( 1, 1 ),
91*> AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2 )
92*> respectively, and so on.
93*> Before entry with UPLO = 'L' or 'l', the array AP must
94*> contain the lower triangular matrix packed sequentially,
95*> column by column, so that AP( 1 ) contains a( 1, 1 ),
96*> AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1 )
97*> respectively, and so on.
98*> Note that when DIAG = 'U' or 'u', the diagonal elements of
99*> A are not referenced, but are assumed to be unity.
100*> \endverbatim
101*>
102*> \param[in,out] X
103*> \verbatim
104*> X is COMPLEX*16 array, dimension at least
105*> ( 1 + ( n - 1 )*abs( INCX ) ).
106*> Before entry, the incremented array X must contain the n
107*> element right-hand side vector b. On exit, X is overwritten
108*> with the solution vector x.
109*> \endverbatim
110*>
111*> \param[in] INCX
112*> \verbatim
113*> INCX is INTEGER
114*> On entry, INCX specifies the increment for the elements of
115*> X. INCX must not be zero.
116*> \endverbatim
117*
118* Authors:
119* ========
120*
121*> \author Univ. of Tennessee
122*> \author Univ. of California Berkeley
123*> \author Univ. of Colorado Denver
124*> \author NAG Ltd.
125*
126*> \ingroup tpsv
127*
128*> \par Further Details:
129* =====================
130*>
131*> \verbatim
132*>
133*> Level 2 Blas routine.
134*>
135*> -- Written on 22-October-1986.
136*> Jack Dongarra, Argonne National Lab.
137*> Jeremy Du Croz, Nag Central Office.
138*> Sven Hammarling, Nag Central Office.
139*> Richard Hanson, Sandia National Labs.
140*> \endverbatim
141*>
142* =====================================================================
143 SUBROUTINE ztpsv(UPLO,TRANS,DIAG,N,AP,X,INCX)
144*
145* -- Reference BLAS level2 routine --
146* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
147* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148*
149* .. Scalar Arguments ..
150 INTEGER INCX,N
151 CHARACTER DIAG,TRANS,UPLO
152* ..
153* .. Array Arguments ..
154 COMPLEX*16 AP(*),X(*)
155* ..
156*
157* =====================================================================
158*
159* .. Parameters ..
160 COMPLEX*16 ZERO
161 parameter(zero= (0.0d+0,0.0d+0))
162* ..
163* .. Local Scalars ..
164 COMPLEX*16 TEMP
165 INTEGER I,INFO,IX,J,JX,K,KK,KX
166 LOGICAL NOCONJ,NOUNIT
167* ..
168* .. External Functions ..
169 LOGICAL LSAME
170 EXTERNAL lsame
171* ..
172* .. External Subroutines ..
173 EXTERNAL xerbla
174* ..
175* .. Intrinsic Functions ..
176 INTRINSIC dconjg
177* ..
178*
179* Test the input parameters.
180*
181 info = 0
182 IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
183 info = 1
184 ELSE IF (.NOT.lsame(trans,'N') .AND.
185 + .NOT.lsame(trans,'T') .AND.
186 + .NOT.lsame(trans,'C')) THEN
187 info = 2
188 ELSE IF (.NOT.lsame(diag,'U') .AND.
189 + .NOT.lsame(diag,'N')) THEN
190 info = 3
191 ELSE IF (n.LT.0) THEN
192 info = 4
193 ELSE IF (incx.EQ.0) THEN
194 info = 7
195 END IF
196 IF (info.NE.0) THEN
197 CALL xerbla('ZTPSV ',info)
198 RETURN
199 END IF
200*
201* Quick return if possible.
202*
203 IF (n.EQ.0) RETURN
204*
205 noconj = lsame(trans,'T')
206 nounit = lsame(diag,'N')
207*
208* Set up the start point in X if the increment is not unity. This
209* will be ( N - 1 )*INCX too small for descending loops.
210*
211 IF (incx.LE.0) THEN
212 kx = 1 - (n-1)*incx
213 ELSE IF (incx.NE.1) THEN
214 kx = 1
215 END IF
216*
217* Start the operations. In this version the elements of AP are
218* accessed sequentially with one pass through AP.
219*
220 IF (lsame(trans,'N')) THEN
221*
222* Form x := inv( A )*x.
223*
224 IF (lsame(uplo,'U')) THEN
225 kk = (n* (n+1))/2
226 IF (incx.EQ.1) THEN
227 DO 20 j = n,1,-1
228 IF (x(j).NE.zero) THEN
229 IF (nounit) x(j) = x(j)/ap(kk)
230 temp = x(j)
231 k = kk - 1
232 DO 10 i = j - 1,1,-1
233 x(i) = x(i) - temp*ap(k)
234 k = k - 1
235 10 CONTINUE
236 END IF
237 kk = kk - j
238 20 CONTINUE
239 ELSE
240 jx = kx + (n-1)*incx
241 DO 40 j = n,1,-1
242 IF (x(jx).NE.zero) THEN
243 IF (nounit) x(jx) = x(jx)/ap(kk)
244 temp = x(jx)
245 ix = jx
246 DO 30 k = kk - 1,kk - j + 1,-1
247 ix = ix - incx
248 x(ix) = x(ix) - temp*ap(k)
249 30 CONTINUE
250 END IF
251 jx = jx - incx
252 kk = kk - j
253 40 CONTINUE
254 END IF
255 ELSE
256 kk = 1
257 IF (incx.EQ.1) THEN
258 DO 60 j = 1,n
259 IF (x(j).NE.zero) THEN
260 IF (nounit) x(j) = x(j)/ap(kk)
261 temp = x(j)
262 k = kk + 1
263 DO 50 i = j + 1,n
264 x(i) = x(i) - temp*ap(k)
265 k = k + 1
266 50 CONTINUE
267 END IF
268 kk = kk + (n-j+1)
269 60 CONTINUE
270 ELSE
271 jx = kx
272 DO 80 j = 1,n
273 IF (x(jx).NE.zero) THEN
274 IF (nounit) x(jx) = x(jx)/ap(kk)
275 temp = x(jx)
276 ix = jx
277 DO 70 k = kk + 1,kk + n - j
278 ix = ix + incx
279 x(ix) = x(ix) - temp*ap(k)
280 70 CONTINUE
281 END IF
282 jx = jx + incx
283 kk = kk + (n-j+1)
284 80 CONTINUE
285 END IF
286 END IF
287 ELSE
288*
289* Form x := inv( A**T )*x or x := inv( A**H )*x.
290*
291 IF (lsame(uplo,'U')) THEN
292 kk = 1
293 IF (incx.EQ.1) THEN
294 DO 110 j = 1,n
295 temp = x(j)
296 k = kk
297 IF (noconj) THEN
298 DO 90 i = 1,j - 1
299 temp = temp - ap(k)*x(i)
300 k = k + 1
301 90 CONTINUE
302 IF (nounit) temp = temp/ap(kk+j-1)
303 ELSE
304 DO 100 i = 1,j - 1
305 temp = temp - dconjg(ap(k))*x(i)
306 k = k + 1
307 100 CONTINUE
308 IF (nounit) temp = temp/dconjg(ap(kk+j-1))
309 END IF
310 x(j) = temp
311 kk = kk + j
312 110 CONTINUE
313 ELSE
314 jx = kx
315 DO 140 j = 1,n
316 temp = x(jx)
317 ix = kx
318 IF (noconj) THEN
319 DO 120 k = kk,kk + j - 2
320 temp = temp - ap(k)*x(ix)
321 ix = ix + incx
322 120 CONTINUE
323 IF (nounit) temp = temp/ap(kk+j-1)
324 ELSE
325 DO 130 k = kk,kk + j - 2
326 temp = temp - dconjg(ap(k))*x(ix)
327 ix = ix + incx
328 130 CONTINUE
329 IF (nounit) temp = temp/dconjg(ap(kk+j-1))
330 END IF
331 x(jx) = temp
332 jx = jx + incx
333 kk = kk + j
334 140 CONTINUE
335 END IF
336 ELSE
337 kk = (n* (n+1))/2
338 IF (incx.EQ.1) THEN
339 DO 170 j = n,1,-1
340 temp = x(j)
341 k = kk
342 IF (noconj) THEN
343 DO 150 i = n,j + 1,-1
344 temp = temp - ap(k)*x(i)
345 k = k - 1
346 150 CONTINUE
347 IF (nounit) temp = temp/ap(kk-n+j)
348 ELSE
349 DO 160 i = n,j + 1,-1
350 temp = temp - dconjg(ap(k))*x(i)
351 k = k - 1
352 160 CONTINUE
353 IF (nounit) temp = temp/dconjg(ap(kk-n+j))
354 END IF
355 x(j) = temp
356 kk = kk - (n-j+1)
357 170 CONTINUE
358 ELSE
359 kx = kx + (n-1)*incx
360 jx = kx
361 DO 200 j = n,1,-1
362 temp = x(jx)
363 ix = kx
364 IF (noconj) THEN
365 DO 180 k = kk,kk - (n- (j+1)),-1
366 temp = temp - ap(k)*x(ix)
367 ix = ix - incx
368 180 CONTINUE
369 IF (nounit) temp = temp/ap(kk-n+j)
370 ELSE
371 DO 190 k = kk,kk - (n- (j+1)),-1
372 temp = temp - dconjg(ap(k))*x(ix)
373 ix = ix - incx
374 190 CONTINUE
375 IF (nounit) temp = temp/dconjg(ap(kk-n+j))
376 END IF
377 x(jx) = temp
378 jx = jx - incx
379 kk = kk - (n-j+1)
380 200 CONTINUE
381 END IF
382 END IF
383 END IF
384*
385 RETURN
386*
387* End of ZTPSV
388*
389 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ztpsv(uplo, trans, diag, n, ap, x, incx)
ZTPSV
Definition ztpsv.f:144