LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zsytrs.f
Go to the documentation of this file.
1*> \brief \b ZSYTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZSYTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zsytrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zsytrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZSYTRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, LDB, N, NRHS
24* ..
25* .. Array Arguments ..
26* INTEGER IPIV( * )
27* COMPLEX*16 A( LDA, * ), B( LDB, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZSYTRS solves a system of linear equations A*X = B with a complex
37*> symmetric matrix A using the factorization A = U*D*U**T or
38*> A = L*D*L**T computed by ZSYTRF.
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] UPLO
45*> \verbatim
46*> UPLO is CHARACTER*1
47*> Specifies whether the details of the factorization are stored
48*> as an upper or lower triangular matrix.
49*> = 'U': Upper triangular, form is A = U*D*U**T;
50*> = 'L': Lower triangular, form is A = L*D*L**T.
51*> \endverbatim
52*>
53*> \param[in] N
54*> \verbatim
55*> N is INTEGER
56*> The order of the matrix A. N >= 0.
57*> \endverbatim
58*>
59*> \param[in] NRHS
60*> \verbatim
61*> NRHS is INTEGER
62*> The number of right hand sides, i.e., the number of columns
63*> of the matrix B. NRHS >= 0.
64*> \endverbatim
65*>
66*> \param[in] A
67*> \verbatim
68*> A is COMPLEX*16 array, dimension (LDA,N)
69*> The block diagonal matrix D and the multipliers used to
70*> obtain the factor U or L as computed by ZSYTRF.
71*> \endverbatim
72*>
73*> \param[in] LDA
74*> \verbatim
75*> LDA is INTEGER
76*> The leading dimension of the array A. LDA >= max(1,N).
77*> \endverbatim
78*>
79*> \param[in] IPIV
80*> \verbatim
81*> IPIV is INTEGER array, dimension (N)
82*> Details of the interchanges and the block structure of D
83*> as determined by ZSYTRF.
84*> \endverbatim
85*>
86*> \param[in,out] B
87*> \verbatim
88*> B is COMPLEX*16 array, dimension (LDB,NRHS)
89*> On entry, the right hand side matrix B.
90*> On exit, the solution matrix X.
91*> \endverbatim
92*>
93*> \param[in] LDB
94*> \verbatim
95*> LDB is INTEGER
96*> The leading dimension of the array B. LDB >= max(1,N).
97*> \endverbatim
98*>
99*> \param[out] INFO
100*> \verbatim
101*> INFO is INTEGER
102*> = 0: successful exit
103*> < 0: if INFO = -i, the i-th argument had an illegal value
104*> \endverbatim
105*
106* Authors:
107* ========
108*
109*> \author Univ. of Tennessee
110*> \author Univ. of California Berkeley
111*> \author Univ. of Colorado Denver
112*> \author NAG Ltd.
113*
114*> \ingroup hetrs
115*
116* =====================================================================
117 SUBROUTINE zsytrs( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
118*
119* -- LAPACK computational routine --
120* -- LAPACK is a software package provided by Univ. of Tennessee, --
121* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
122*
123* .. Scalar Arguments ..
124 CHARACTER UPLO
125 INTEGER INFO, LDA, LDB, N, NRHS
126* ..
127* .. Array Arguments ..
128 INTEGER IPIV( * )
129 COMPLEX*16 A( LDA, * ), B( LDB, * )
130* ..
131*
132* =====================================================================
133*
134* .. Parameters ..
135 COMPLEX*16 ONE
136 parameter( one = ( 1.0d+0, 0.0d+0 ) )
137* ..
138* .. Local Scalars ..
139 LOGICAL UPPER
140 INTEGER J, K, KP
141 COMPLEX*16 AK, AKM1, AKM1K, BK, BKM1, DENOM
142* ..
143* .. External Functions ..
144 LOGICAL LSAME
145 EXTERNAL lsame
146* ..
147* .. External Subroutines ..
148 EXTERNAL xerbla, zgemv, zgeru, zscal, zswap
149* ..
150* .. Intrinsic Functions ..
151 INTRINSIC max
152* ..
153* .. Executable Statements ..
154*
155 info = 0
156 upper = lsame( uplo, 'U' )
157 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
158 info = -1
159 ELSE IF( n.LT.0 ) THEN
160 info = -2
161 ELSE IF( nrhs.LT.0 ) THEN
162 info = -3
163 ELSE IF( lda.LT.max( 1, n ) ) THEN
164 info = -5
165 ELSE IF( ldb.LT.max( 1, n ) ) THEN
166 info = -8
167 END IF
168 IF( info.NE.0 ) THEN
169 CALL xerbla( 'ZSYTRS', -info )
170 RETURN
171 END IF
172*
173* Quick return if possible
174*
175 IF( n.EQ.0 .OR. nrhs.EQ.0 )
176 $ RETURN
177*
178 IF( upper ) THEN
179*
180* Solve A*X = B, where A = U*D*U**T.
181*
182* First solve U*D*X = B, overwriting B with X.
183*
184* K is the main loop index, decreasing from N to 1 in steps of
185* 1 or 2, depending on the size of the diagonal blocks.
186*
187 k = n
188 10 CONTINUE
189*
190* If K < 1, exit from loop.
191*
192 IF( k.LT.1 )
193 $ GO TO 30
194*
195 IF( ipiv( k ).GT.0 ) THEN
196*
197* 1 x 1 diagonal block
198*
199* Interchange rows K and IPIV(K).
200*
201 kp = ipiv( k )
202 IF( kp.NE.k )
203 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
204*
205* Multiply by inv(U(K)), where U(K) is the transformation
206* stored in column K of A.
207*
208 CALL zgeru( k-1, nrhs, -one, a( 1, k ), 1, b( k, 1 ),
209 $ ldb,
210 $ b( 1, 1 ), ldb )
211*
212* Multiply by the inverse of the diagonal block.
213*
214 CALL zscal( nrhs, one / a( k, k ), b( k, 1 ), ldb )
215 k = k - 1
216 ELSE
217*
218* 2 x 2 diagonal block
219*
220* Interchange rows K-1 and -IPIV(K).
221*
222 kp = -ipiv( k )
223 IF( kp.NE.k-1 )
224 $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
225*
226* Multiply by inv(U(K)), where U(K) is the transformation
227* stored in columns K-1 and K of A.
228*
229 CALL zgeru( k-2, nrhs, -one, a( 1, k ), 1, b( k, 1 ),
230 $ ldb,
231 $ b( 1, 1 ), ldb )
232 CALL zgeru( k-2, nrhs, -one, a( 1, k-1 ), 1, b( k-1, 1 ),
233 $ ldb, b( 1, 1 ), ldb )
234*
235* Multiply by the inverse of the diagonal block.
236*
237 akm1k = a( k-1, k )
238 akm1 = a( k-1, k-1 ) / akm1k
239 ak = a( k, k ) / akm1k
240 denom = akm1*ak - one
241 DO 20 j = 1, nrhs
242 bkm1 = b( k-1, j ) / akm1k
243 bk = b( k, j ) / akm1k
244 b( k-1, j ) = ( ak*bkm1-bk ) / denom
245 b( k, j ) = ( akm1*bk-bkm1 ) / denom
246 20 CONTINUE
247 k = k - 2
248 END IF
249*
250 GO TO 10
251 30 CONTINUE
252*
253* Next solve U**T *X = B, overwriting B with X.
254*
255* K is the main loop index, increasing from 1 to N in steps of
256* 1 or 2, depending on the size of the diagonal blocks.
257*
258 k = 1
259 40 CONTINUE
260*
261* If K > N, exit from loop.
262*
263 IF( k.GT.n )
264 $ GO TO 50
265*
266 IF( ipiv( k ).GT.0 ) THEN
267*
268* 1 x 1 diagonal block
269*
270* Multiply by inv(U**T(K)), where U(K) is the transformation
271* stored in column K of A.
272*
273 CALL zgemv( 'Transpose', k-1, nrhs, -one, b, ldb, a( 1,
274 $ k ),
275 $ 1, one, b( k, 1 ), ldb )
276*
277* Interchange rows K and IPIV(K).
278*
279 kp = ipiv( k )
280 IF( kp.NE.k )
281 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
282 k = k + 1
283 ELSE
284*
285* 2 x 2 diagonal block
286*
287* Multiply by inv(U**T(K+1)), where U(K+1) is the transformation
288* stored in columns K and K+1 of A.
289*
290 CALL zgemv( 'Transpose', k-1, nrhs, -one, b, ldb, a( 1,
291 $ k ),
292 $ 1, one, b( k, 1 ), ldb )
293 CALL zgemv( 'Transpose', k-1, nrhs, -one, b, ldb,
294 $ a( 1, k+1 ), 1, one, b( k+1, 1 ), ldb )
295*
296* Interchange rows K and -IPIV(K).
297*
298 kp = -ipiv( k )
299 IF( kp.NE.k )
300 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
301 k = k + 2
302 END IF
303*
304 GO TO 40
305 50 CONTINUE
306*
307 ELSE
308*
309* Solve A*X = B, where A = L*D*L**T.
310*
311* First solve L*D*X = B, overwriting B with X.
312*
313* K is the main loop index, increasing from 1 to N in steps of
314* 1 or 2, depending on the size of the diagonal blocks.
315*
316 k = 1
317 60 CONTINUE
318*
319* If K > N, exit from loop.
320*
321 IF( k.GT.n )
322 $ GO TO 80
323*
324 IF( ipiv( k ).GT.0 ) THEN
325*
326* 1 x 1 diagonal block
327*
328* Interchange rows K and IPIV(K).
329*
330 kp = ipiv( k )
331 IF( kp.NE.k )
332 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
333*
334* Multiply by inv(L(K)), where L(K) is the transformation
335* stored in column K of A.
336*
337 IF( k.LT.n )
338 $ CALL zgeru( n-k, nrhs, -one, a( k+1, k ), 1, b( k,
339 $ 1 ),
340 $ ldb, b( k+1, 1 ), ldb )
341*
342* Multiply by the inverse of the diagonal block.
343*
344 CALL zscal( nrhs, one / a( k, k ), b( k, 1 ), ldb )
345 k = k + 1
346 ELSE
347*
348* 2 x 2 diagonal block
349*
350* Interchange rows K+1 and -IPIV(K).
351*
352 kp = -ipiv( k )
353 IF( kp.NE.k+1 )
354 $ CALL zswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ), ldb )
355*
356* Multiply by inv(L(K)), where L(K) is the transformation
357* stored in columns K and K+1 of A.
358*
359 IF( k.LT.n-1 ) THEN
360 CALL zgeru( n-k-1, nrhs, -one, a( k+2, k ), 1, b( k,
361 $ 1 ),
362 $ ldb, b( k+2, 1 ), ldb )
363 CALL zgeru( n-k-1, nrhs, -one, a( k+2, k+1 ), 1,
364 $ b( k+1, 1 ), ldb, b( k+2, 1 ), ldb )
365 END IF
366*
367* Multiply by the inverse of the diagonal block.
368*
369 akm1k = a( k+1, k )
370 akm1 = a( k, k ) / akm1k
371 ak = a( k+1, k+1 ) / akm1k
372 denom = akm1*ak - one
373 DO 70 j = 1, nrhs
374 bkm1 = b( k, j ) / akm1k
375 bk = b( k+1, j ) / akm1k
376 b( k, j ) = ( ak*bkm1-bk ) / denom
377 b( k+1, j ) = ( akm1*bk-bkm1 ) / denom
378 70 CONTINUE
379 k = k + 2
380 END IF
381*
382 GO TO 60
383 80 CONTINUE
384*
385* Next solve L**T *X = B, overwriting B with X.
386*
387* K is the main loop index, decreasing from N to 1 in steps of
388* 1 or 2, depending on the size of the diagonal blocks.
389*
390 k = n
391 90 CONTINUE
392*
393* If K < 1, exit from loop.
394*
395 IF( k.LT.1 )
396 $ GO TO 100
397*
398 IF( ipiv( k ).GT.0 ) THEN
399*
400* 1 x 1 diagonal block
401*
402* Multiply by inv(L**T(K)), where L(K) is the transformation
403* stored in column K of A.
404*
405 IF( k.LT.n )
406 $ CALL zgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
407 $ ldb, a( k+1, k ), 1, one, b( k, 1 ), ldb )
408*
409* Interchange rows K and IPIV(K).
410*
411 kp = ipiv( k )
412 IF( kp.NE.k )
413 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
414 k = k - 1
415 ELSE
416*
417* 2 x 2 diagonal block
418*
419* Multiply by inv(L**T(K-1)), where L(K-1) is the transformation
420* stored in columns K-1 and K of A.
421*
422 IF( k.LT.n ) THEN
423 CALL zgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
424 $ ldb, a( k+1, k ), 1, one, b( k, 1 ), ldb )
425 CALL zgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
426 $ ldb, a( k+1, k-1 ), 1, one, b( k-1, 1 ),
427 $ ldb )
428 END IF
429*
430* Interchange rows K and -IPIV(K).
431*
432 kp = -ipiv( k )
433 IF( kp.NE.k )
434 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
435 k = k - 2
436 END IF
437*
438 GO TO 90
439 100 CONTINUE
440 END IF
441*
442 RETURN
443*
444* End of ZSYTRS
445*
446 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zgeru(m, n, alpha, x, incx, y, incy, a, lda)
ZGERU
Definition zgeru.f:130
subroutine zsytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
ZSYTRS
Definition zsytrs.f:118
subroutine zscal(n, za, zx, incx)
ZSCAL
Definition zscal.f:78
subroutine zswap(n, zx, incx, zy, incy)
ZSWAP
Definition zswap.f:81