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