LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zsytrs ( character  UPLO,
integer  N,
integer  NRHS,
complex*16, dimension( lda, * )  A,
integer  LDA,
integer, dimension( * )  IPIV,
complex*16, dimension( ldb, * )  B,
integer  LDB,
integer  INFO 
)

ZSYTRS

Download ZSYTRS + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZSYTRS solves a system of linear equations A*X = B with a complex
 symmetric matrix A using the factorization A = U*D*U**T or
 A = L*D*L**T computed by ZSYTRF.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the details of the factorization are stored
          as an upper or lower triangular matrix.
          = 'U':  Upper triangular, form is A = U*D*U**T;
          = 'L':  Lower triangular, form is A = L*D*L**T.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]NRHS
          NRHS is INTEGER
          The number of right hand sides, i.e., the number of columns
          of the matrix B.  NRHS >= 0.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by ZSYTRF.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          Details of the interchanges and the block structure of D
          as determined by ZSYTRF.
[in,out]B
          B is COMPLEX*16 array, dimension (LDB,NRHS)
          On entry, the right hand side matrix B.
          On exit, the solution matrix X.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(1,N).
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 122 of file zsytrs.f.

122 *
123 * -- LAPACK computational routine (version 3.4.0) --
124 * -- LAPACK is a software package provided by Univ. of Tennessee, --
125 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126 * November 2011
127 *
128 * .. Scalar Arguments ..
129  CHARACTER uplo
130  INTEGER info, lda, ldb, n, nrhs
131 * ..
132 * .. Array Arguments ..
133  INTEGER ipiv( * )
134  COMPLEX*16 a( lda, * ), b( ldb, * )
135 * ..
136 *
137 * =====================================================================
138 *
139 * .. Parameters ..
140  COMPLEX*16 one
141  parameter ( one = ( 1.0d+0, 0.0d+0 ) )
142 * ..
143 * .. Local Scalars ..
144  LOGICAL upper
145  INTEGER j, k, kp
146  COMPLEX*16 ak, akm1, akm1k, bk, bkm1, denom
147 * ..
148 * .. External Functions ..
149  LOGICAL lsame
150  EXTERNAL lsame
151 * ..
152 * .. External Subroutines ..
153  EXTERNAL xerbla, zgemv, zgeru, zscal, zswap
154 * ..
155 * .. Intrinsic Functions ..
156  INTRINSIC max
157 * ..
158 * .. Executable Statements ..
159 *
160  info = 0
161  upper = lsame( uplo, 'U' )
162  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
163  info = -1
164  ELSE IF( n.LT.0 ) THEN
165  info = -2
166  ELSE IF( nrhs.LT.0 ) THEN
167  info = -3
168  ELSE IF( lda.LT.max( 1, n ) ) THEN
169  info = -5
170  ELSE IF( ldb.LT.max( 1, n ) ) THEN
171  info = -8
172  END IF
173  IF( info.NE.0 ) THEN
174  CALL xerbla( 'ZSYTRS', -info )
175  RETURN
176  END IF
177 *
178 * Quick return if possible
179 *
180  IF( n.EQ.0 .OR. nrhs.EQ.0 )
181  $ RETURN
182 *
183  IF( upper ) THEN
184 *
185 * Solve A*X = B, where A = U*D*U**T.
186 *
187 * First solve U*D*X = B, overwriting B with X.
188 *
189 * K is the main loop index, decreasing from N to 1 in steps of
190 * 1 or 2, depending on the size of the diagonal blocks.
191 *
192  k = n
193  10 CONTINUE
194 *
195 * If K < 1, exit from loop.
196 *
197  IF( k.LT.1 )
198  $ GO TO 30
199 *
200  IF( ipiv( k ).GT.0 ) THEN
201 *
202 * 1 x 1 diagonal block
203 *
204 * Interchange rows K and IPIV(K).
205 *
206  kp = ipiv( k )
207  IF( kp.NE.k )
208  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
209 *
210 * Multiply by inv(U(K)), where U(K) is the transformation
211 * stored in column K of A.
212 *
213  CALL zgeru( k-1, nrhs, -one, a( 1, k ), 1, b( k, 1 ), ldb,
214  $ b( 1, 1 ), ldb )
215 *
216 * Multiply by the inverse of the diagonal block.
217 *
218  CALL zscal( nrhs, one / a( k, k ), b( k, 1 ), ldb )
219  k = k - 1
220  ELSE
221 *
222 * 2 x 2 diagonal block
223 *
224 * Interchange rows K-1 and -IPIV(K).
225 *
226  kp = -ipiv( k )
227  IF( kp.NE.k-1 )
228  $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
229 *
230 * Multiply by inv(U(K)), where U(K) is the transformation
231 * stored in columns K-1 and K of A.
232 *
233  CALL zgeru( k-2, nrhs, -one, a( 1, k ), 1, b( k, 1 ), ldb,
234  $ b( 1, 1 ), ldb )
235  CALL zgeru( k-2, nrhs, -one, a( 1, k-1 ), 1, b( k-1, 1 ),
236  $ ldb, b( 1, 1 ), ldb )
237 *
238 * Multiply by the inverse of the diagonal block.
239 *
240  akm1k = a( k-1, k )
241  akm1 = a( k-1, k-1 ) / akm1k
242  ak = a( k, k ) / akm1k
243  denom = akm1*ak - one
244  DO 20 j = 1, nrhs
245  bkm1 = b( k-1, j ) / akm1k
246  bk = b( k, j ) / akm1k
247  b( k-1, j ) = ( ak*bkm1-bk ) / denom
248  b( k, j ) = ( akm1*bk-bkm1 ) / denom
249  20 CONTINUE
250  k = k - 2
251  END IF
252 *
253  GO TO 10
254  30 CONTINUE
255 *
256 * Next solve U**T *X = B, overwriting B with X.
257 *
258 * K is the main loop index, increasing from 1 to N in steps of
259 * 1 or 2, depending on the size of the diagonal blocks.
260 *
261  k = 1
262  40 CONTINUE
263 *
264 * If K > N, exit from loop.
265 *
266  IF( k.GT.n )
267  $ GO TO 50
268 *
269  IF( ipiv( k ).GT.0 ) THEN
270 *
271 * 1 x 1 diagonal block
272 *
273 * Multiply by inv(U**T(K)), where U(K) is the transformation
274 * stored in column K of A.
275 *
276  CALL zgemv( 'Transpose', k-1, nrhs, -one, b, ldb, a( 1, k ),
277  $ 1, one, b( k, 1 ), ldb )
278 *
279 * Interchange rows K and IPIV(K).
280 *
281  kp = ipiv( k )
282  IF( kp.NE.k )
283  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
284  k = k + 1
285  ELSE
286 *
287 * 2 x 2 diagonal block
288 *
289 * Multiply by inv(U**T(K+1)), where U(K+1) is the transformation
290 * stored in columns K and K+1 of A.
291 *
292  CALL zgemv( 'Transpose', k-1, nrhs, -one, b, ldb, a( 1, k ),
293  $ 1, one, b( k, 1 ), ldb )
294  CALL zgemv( 'Transpose', k-1, nrhs, -one, b, ldb,
295  $ a( 1, k+1 ), 1, one, b( k+1, 1 ), ldb )
296 *
297 * Interchange rows K and -IPIV(K).
298 *
299  kp = -ipiv( k )
300  IF( kp.NE.k )
301  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
302  k = k + 2
303  END IF
304 *
305  GO TO 40
306  50 CONTINUE
307 *
308  ELSE
309 *
310 * Solve A*X = B, where A = L*D*L**T.
311 *
312 * First solve L*D*X = B, overwriting B with X.
313 *
314 * K is the main loop index, increasing from 1 to N in steps of
315 * 1 or 2, depending on the size of the diagonal blocks.
316 *
317  k = 1
318  60 CONTINUE
319 *
320 * If K > N, exit from loop.
321 *
322  IF( k.GT.n )
323  $ GO TO 80
324 *
325  IF( ipiv( k ).GT.0 ) THEN
326 *
327 * 1 x 1 diagonal block
328 *
329 * Interchange rows K and IPIV(K).
330 *
331  kp = ipiv( k )
332  IF( kp.NE.k )
333  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
334 *
335 * Multiply by inv(L(K)), where L(K) is the transformation
336 * stored in column K of A.
337 *
338  IF( k.LT.n )
339  $ CALL zgeru( n-k, nrhs, -one, a( k+1, k ), 1, b( k, 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, 1 ),
361  $ ldb, b( k+2, 1 ), ldb )
362  CALL zgeru( n-k-1, nrhs, -one, a( k+2, k+1 ), 1,
363  $ b( k+1, 1 ), ldb, b( k+2, 1 ), ldb )
364  END IF
365 *
366 * Multiply by the inverse of the diagonal block.
367 *
368  akm1k = a( k+1, k )
369  akm1 = a( k, k ) / akm1k
370  ak = a( k+1, k+1 ) / akm1k
371  denom = akm1*ak - one
372  DO 70 j = 1, nrhs
373  bkm1 = b( k, j ) / akm1k
374  bk = b( k+1, j ) / akm1k
375  b( k, j ) = ( ak*bkm1-bk ) / denom
376  b( k+1, j ) = ( akm1*bk-bkm1 ) / denom
377  70 CONTINUE
378  k = k + 2
379  END IF
380 *
381  GO TO 60
382  80 CONTINUE
383 *
384 * Next solve L**T *X = B, overwriting B with X.
385 *
386 * K is the main loop index, decreasing from N to 1 in steps of
387 * 1 or 2, depending on the size of the diagonal blocks.
388 *
389  k = n
390  90 CONTINUE
391 *
392 * If K < 1, exit from loop.
393 *
394  IF( k.LT.1 )
395  $ GO TO 100
396 *
397  IF( ipiv( k ).GT.0 ) THEN
398 *
399 * 1 x 1 diagonal block
400 *
401 * Multiply by inv(L**T(K)), where L(K) is the transformation
402 * stored in column K of A.
403 *
404  IF( k.LT.n )
405  $ CALL zgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
406  $ ldb, a( k+1, k ), 1, one, b( k, 1 ), ldb )
407 *
408 * Interchange rows K and IPIV(K).
409 *
410  kp = ipiv( k )
411  IF( kp.NE.k )
412  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
413  k = k - 1
414  ELSE
415 *
416 * 2 x 2 diagonal block
417 *
418 * Multiply by inv(L**T(K-1)), where L(K-1) is the transformation
419 * stored in columns K-1 and K of A.
420 *
421  IF( k.LT.n ) THEN
422  CALL zgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
423  $ ldb, a( k+1, k ), 1, one, b( k, 1 ), ldb )
424  CALL zgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
425  $ ldb, a( k+1, k-1 ), 1, one, b( k-1, 1 ),
426  $ ldb )
427  END IF
428 *
429 * Interchange rows K and -IPIV(K).
430 *
431  kp = -ipiv( k )
432  IF( kp.NE.k )
433  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
434  k = k - 2
435  END IF
436 *
437  GO TO 90
438  100 CONTINUE
439  END IF
440 *
441  RETURN
442 *
443 * End of ZSYTRS
444 *
subroutine zgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
ZGEMV
Definition: zgemv.f:160
subroutine zswap(N, ZX, INCX, ZY, INCY)
ZSWAP
Definition: zswap.f:52
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zgeru(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
ZGERU
Definition: zgeru.f:132
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine zscal(N, ZA, ZX, INCX)
ZSCAL
Definition: zscal.f:54

Here is the call graph for this function:

Here is the caller graph for this function: