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

CSYTRS2

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

Purpose:
 CSYTRS2 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 CSYTRF and converted by CSYCONV.
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,out]A
          A is COMPLEX array, dimension (LDA,N)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by CSYTRF.
          Note that A is input / output. This might be counter-intuitive,
          and one may think that A is input only. A is input / output. This
          is because, at the start of the subroutine, we permute A in a
          "better" form and then we permute A back to its original form at
          the end.
[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 CSYTRF.
[in,out]B
          B is COMPLEX 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]WORK
          WORK is COMPLEX array, dimension (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 2015

Definition at line 134 of file csytrs2.f.

134 *
135 * -- LAPACK computational routine (version 3.6.0) --
136 * -- LAPACK is a software package provided by Univ. of Tennessee, --
137 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
138 * November 2015
139 *
140 * .. Scalar Arguments ..
141  CHARACTER uplo
142  INTEGER info, lda, ldb, n, nrhs
143 * ..
144 * .. Array Arguments ..
145  INTEGER ipiv( * )
146  COMPLEX a( lda, * ), b( ldb, * ), work( * )
147 * ..
148 *
149 * =====================================================================
150 *
151 * .. Parameters ..
152  COMPLEX one
153  parameter ( one = (1.0e+0,0.0e+0) )
154 * ..
155 * .. Local Scalars ..
156  LOGICAL upper
157  INTEGER i, iinfo, j, k, kp
158  COMPLEX ak, akm1, akm1k, bk, bkm1, denom
159 * ..
160 * .. External Functions ..
161  LOGICAL lsame
162  EXTERNAL lsame
163 * ..
164 * .. External Subroutines ..
165  EXTERNAL cscal, csyconv, cswap, ctrsm, xerbla
166 * ..
167 * .. Intrinsic Functions ..
168  INTRINSIC max
169 * ..
170 * .. Executable Statements ..
171 *
172  info = 0
173  upper = lsame( uplo, 'U' )
174  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
175  info = -1
176  ELSE IF( n.LT.0 ) THEN
177  info = -2
178  ELSE IF( nrhs.LT.0 ) THEN
179  info = -3
180  ELSE IF( lda.LT.max( 1, n ) ) THEN
181  info = -5
182  ELSE IF( ldb.LT.max( 1, n ) ) THEN
183  info = -8
184  END IF
185  IF( info.NE.0 ) THEN
186  CALL xerbla( 'CSYTRS2', -info )
187  RETURN
188  END IF
189 *
190 * Quick return if possible
191 *
192  IF( n.EQ.0 .OR. nrhs.EQ.0 )
193  $ RETURN
194 *
195 * Convert A
196 *
197  CALL csyconv( uplo, 'C', n, a, lda, ipiv, work, iinfo )
198 *
199  IF( upper ) THEN
200 *
201 * Solve A*X = B, where A = U*D*U**T.
202 *
203 * P**T * B
204  k=n
205  DO WHILE ( k .GE. 1 )
206  IF( ipiv( k ).GT.0 ) THEN
207 * 1 x 1 diagonal block
208 * Interchange rows K and IPIV(K).
209  kp = ipiv( k )
210  IF( kp.NE.k )
211  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
212  k=k-1
213  ELSE
214 * 2 x 2 diagonal block
215 * Interchange rows K-1 and -IPIV(K).
216  kp = -ipiv( k )
217  IF( kp.EQ.-ipiv( k-1 ) )
218  $ CALL cswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
219  k=k-2
220  END IF
221  END DO
222 *
223 * Compute (U \P**T * B) -> B [ (U \P**T * B) ]
224 *
225  CALL ctrsm('L','U','N','U',n,nrhs,one,a,lda,b,ldb)
226 *
227 * Compute D \ B -> B [ D \ (U \P**T * B) ]
228 *
229  i=n
230  DO WHILE ( i .GE. 1 )
231  IF( ipiv(i) .GT. 0 ) THEN
232  CALL cscal( nrhs, one / a( i, i ), b( i, 1 ), ldb )
233  ELSEIF ( i .GT. 1) THEN
234  IF ( ipiv(i-1) .EQ. ipiv(i) ) THEN
235  akm1k = work(i)
236  akm1 = a( i-1, i-1 ) / akm1k
237  ak = a( i, i ) / akm1k
238  denom = akm1*ak - one
239  DO 15 j = 1, nrhs
240  bkm1 = b( i-1, j ) / akm1k
241  bk = b( i, j ) / akm1k
242  b( i-1, j ) = ( ak*bkm1-bk ) / denom
243  b( i, j ) = ( akm1*bk-bkm1 ) / denom
244  15 CONTINUE
245  i = i - 1
246  ENDIF
247  ENDIF
248  i = i - 1
249  END DO
250 *
251 * Compute (U**T \ B) -> B [ U**T \ (D \ (U \P**T * B) ) ]
252 *
253  CALL ctrsm('L','U','T','U',n,nrhs,one,a,lda,b,ldb)
254 *
255 * P * B [ P * (U**T \ (D \ (U \P**T * B) )) ]
256 *
257  k=1
258  DO WHILE ( k .LE. n )
259  IF( ipiv( k ).GT.0 ) THEN
260 * 1 x 1 diagonal block
261 * Interchange rows K and IPIV(K).
262  kp = ipiv( k )
263  IF( kp.NE.k )
264  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
265  k=k+1
266  ELSE
267 * 2 x 2 diagonal block
268 * Interchange rows K-1 and -IPIV(K).
269  kp = -ipiv( k )
270  IF( k .LT. n .AND. kp.EQ.-ipiv( k+1 ) )
271  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
272  k=k+2
273  ENDIF
274  END DO
275 *
276  ELSE
277 *
278 * Solve A*X = B, where A = L*D*L**T.
279 *
280 * P**T * B
281  k=1
282  DO WHILE ( k .LE. n )
283  IF( ipiv( k ).GT.0 ) THEN
284 * 1 x 1 diagonal block
285 * Interchange rows K and IPIV(K).
286  kp = ipiv( k )
287  IF( kp.NE.k )
288  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
289  k=k+1
290  ELSE
291 * 2 x 2 diagonal block
292 * Interchange rows K and -IPIV(K+1).
293  kp = -ipiv( k+1 )
294  IF( kp.EQ.-ipiv( k ) )
295  $ CALL cswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ), ldb )
296  k=k+2
297  ENDIF
298  END DO
299 *
300 * Compute (L \P**T * B) -> B [ (L \P**T * B) ]
301 *
302  CALL ctrsm('L','L','N','U',n,nrhs,one,a,lda,b,ldb)
303 *
304 * Compute D \ B -> B [ D \ (L \P**T * B) ]
305 *
306  i=1
307  DO WHILE ( i .LE. n )
308  IF( ipiv(i) .GT. 0 ) THEN
309  CALL cscal( nrhs, one / a( i, i ), b( i, 1 ), ldb )
310  ELSE
311  akm1k = work(i)
312  akm1 = a( i, i ) / akm1k
313  ak = a( i+1, i+1 ) / akm1k
314  denom = akm1*ak - one
315  DO 25 j = 1, nrhs
316  bkm1 = b( i, j ) / akm1k
317  bk = b( i+1, j ) / akm1k
318  b( i, j ) = ( ak*bkm1-bk ) / denom
319  b( i+1, j ) = ( akm1*bk-bkm1 ) / denom
320  25 CONTINUE
321  i = i + 1
322  ENDIF
323  i = i + 1
324  END DO
325 *
326 * Compute (L**T \ B) -> B [ L**T \ (D \ (L \P**T * B) ) ]
327 *
328  CALL ctrsm('L','L','T','U',n,nrhs,one,a,lda,b,ldb)
329 *
330 * P * B [ P * (L**T \ (D \ (L \P**T * B) )) ]
331 *
332  k=n
333  DO WHILE ( k .GE. 1 )
334  IF( ipiv( k ).GT.0 ) THEN
335 * 1 x 1 diagonal block
336 * Interchange rows K and IPIV(K).
337  kp = ipiv( k )
338  IF( kp.NE.k )
339  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
340  k=k-1
341  ELSE
342 * 2 x 2 diagonal block
343 * Interchange rows K-1 and -IPIV(K).
344  kp = -ipiv( k )
345  IF( k.GT.1 .AND. kp.EQ.-ipiv( k-1 ) )
346  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
347  k=k-2
348  ENDIF
349  END DO
350 *
351  END IF
352 *
353 * Revert A
354 *
355  CALL csyconv( uplo, 'R', n, a, lda, ipiv, work, iinfo )
356 *
357  RETURN
358 *
359 * End of CSYTRS2
360 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cscal(N, CA, CX, INCX)
CSCAL
Definition: cscal.f:54
subroutine ctrsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRSM
Definition: ctrsm.f:182
subroutine csyconv(UPLO, WAY, N, A, LDA, IPIV, E, INFO)
CSYCONV
Definition: csyconv.f:116
subroutine cswap(N, CX, INCX, CY, INCY)
CSWAP
Definition: cswap.f:52
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: