LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine csptrs ( character  UPLO,
integer  N,
integer  NRHS,
complex, dimension( * )  AP,
integer, dimension( * )  IPIV,
complex, dimension( ldb, * )  B,
integer  LDB,
integer  INFO 
)

CSPTRS

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

Purpose:
 CSPTRS solves a system of linear equations A*X = B with a complex
 symmetric matrix A stored in packed format using the factorization
 A = U*D*U**T or A = L*D*L**T computed by CSPTRF.
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]AP
          AP is COMPLEX array, dimension (N*(N+1)/2)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by CSPTRF, stored as a
          packed triangular matrix.
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          Details of the interchanges and the block structure of D
          as determined by CSPTRF.
[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]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 117 of file csptrs.f.

117 *
118 * -- LAPACK computational routine (version 3.4.0) --
119 * -- LAPACK is a software package provided by Univ. of Tennessee, --
120 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
121 * November 2011
122 *
123 * .. Scalar Arguments ..
124  CHARACTER uplo
125  INTEGER info, ldb, n, nrhs
126 * ..
127 * .. Array Arguments ..
128  INTEGER ipiv( * )
129  COMPLEX ap( * ), b( ldb, * )
130 * ..
131 *
132 * =====================================================================
133 *
134 * .. Parameters ..
135  COMPLEX one
136  parameter ( one = ( 1.0e+0, 0.0e+0 ) )
137 * ..
138 * .. Local Scalars ..
139  LOGICAL upper
140  INTEGER j, k, kc, kp
141  COMPLEX ak, akm1, akm1k, bk, bkm1, denom
142 * ..
143 * .. External Functions ..
144  LOGICAL lsame
145  EXTERNAL lsame
146 * ..
147 * .. External Subroutines ..
148  EXTERNAL cgemv, cgeru, cscal, cswap, xerbla
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( ldb.LT.max( 1, n ) ) THEN
164  info = -7
165  END IF
166  IF( info.NE.0 ) THEN
167  CALL xerbla( 'CSPTRS', -info )
168  RETURN
169  END IF
170 *
171 * Quick return if possible
172 *
173  IF( n.EQ.0 .OR. nrhs.EQ.0 )
174  $ RETURN
175 *
176  IF( upper ) THEN
177 *
178 * Solve A*X = B, where A = U*D*U**T.
179 *
180 * First solve U*D*X = B, overwriting B with X.
181 *
182 * K is the main loop index, decreasing from N to 1 in steps of
183 * 1 or 2, depending on the size of the diagonal blocks.
184 *
185  k = n
186  kc = n*( n+1 ) / 2 + 1
187  10 CONTINUE
188 *
189 * If K < 1, exit from loop.
190 *
191  IF( k.LT.1 )
192  $ GO TO 30
193 *
194  kc = kc - k
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 cswap( 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 cgeru( k-1, nrhs, -one, ap( kc ), 1, b( k, 1 ), ldb,
209  $ b( 1, 1 ), ldb )
210 *
211 * Multiply by the inverse of the diagonal block.
212 *
213  CALL cscal( nrhs, one / ap( kc+k-1 ), b( k, 1 ), ldb )
214  k = k - 1
215  ELSE
216 *
217 * 2 x 2 diagonal block
218 *
219 * Interchange rows K-1 and -IPIV(K).
220 *
221  kp = -ipiv( k )
222  IF( kp.NE.k-1 )
223  $ CALL cswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
224 *
225 * Multiply by inv(U(K)), where U(K) is the transformation
226 * stored in columns K-1 and K of A.
227 *
228  CALL cgeru( k-2, nrhs, -one, ap( kc ), 1, b( k, 1 ), ldb,
229  $ b( 1, 1 ), ldb )
230  CALL cgeru( k-2, nrhs, -one, ap( kc-( k-1 ) ), 1,
231  $ b( k-1, 1 ), ldb, b( 1, 1 ), ldb )
232 *
233 * Multiply by the inverse of the diagonal block.
234 *
235  akm1k = ap( kc+k-2 )
236  akm1 = ap( kc-1 ) / akm1k
237  ak = ap( kc+k-1 ) / akm1k
238  denom = akm1*ak - one
239  DO 20 j = 1, nrhs
240  bkm1 = b( k-1, j ) / akm1k
241  bk = b( k, j ) / akm1k
242  b( k-1, j ) = ( ak*bkm1-bk ) / denom
243  b( k, j ) = ( akm1*bk-bkm1 ) / denom
244  20 CONTINUE
245  kc = kc - k + 1
246  k = k - 2
247  END IF
248 *
249  GO TO 10
250  30 CONTINUE
251 *
252 * Next solve U**T*X = B, overwriting B with X.
253 *
254 * K is the main loop index, increasing from 1 to N in steps of
255 * 1 or 2, depending on the size of the diagonal blocks.
256 *
257  k = 1
258  kc = 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, ap( kc ),
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  kc = kc + k
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 cgemv( 'Transpose', k-1, nrhs, -one, b, ldb, ap( kc ),
291  $ 1, one, b( k, 1 ), ldb )
292  CALL cgemv( 'Transpose', k-1, nrhs, -one, b, ldb,
293  $ ap( kc+k ), 1, one, b( k+1, 1 ), ldb )
294 *
295 * Interchange rows K and -IPIV(K).
296 *
297  kp = -ipiv( k )
298  IF( kp.NE.k )
299  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
300  kc = kc + 2*k + 1
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  kc = 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 cswap( 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 cgeru( n-k, nrhs, -one, ap( kc+1 ), 1, b( k, 1 ),
340  $ ldb, b( k+1, 1 ), ldb )
341 *
342 * Multiply by the inverse of the diagonal block.
343 *
344  CALL cscal( nrhs, one / ap( kc ), b( k, 1 ), ldb )
345  kc = kc + n - k + 1
346  k = k + 1
347  ELSE
348 *
349 * 2 x 2 diagonal block
350 *
351 * Interchange rows K+1 and -IPIV(K).
352 *
353  kp = -ipiv( k )
354  IF( kp.NE.k+1 )
355  $ CALL cswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ), ldb )
356 *
357 * Multiply by inv(L(K)), where L(K) is the transformation
358 * stored in columns K and K+1 of A.
359 *
360  IF( k.LT.n-1 ) THEN
361  CALL cgeru( n-k-1, nrhs, -one, ap( kc+2 ), 1, b( k, 1 ),
362  $ ldb, b( k+2, 1 ), ldb )
363  CALL cgeru( n-k-1, nrhs, -one, ap( kc+n-k+2 ), 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 = ap( kc+1 )
370  akm1 = ap( kc ) / akm1k
371  ak = ap( kc+n-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  kc = kc + 2*( n-k ) + 1
380  k = k + 2
381  END IF
382 *
383  GO TO 60
384  80 CONTINUE
385 *
386 * Next solve L**T*X = B, overwriting B with X.
387 *
388 * K is the main loop index, decreasing from N to 1 in steps of
389 * 1 or 2, depending on the size of the diagonal blocks.
390 *
391  k = n
392  kc = n*( n+1 ) / 2 + 1
393  90 CONTINUE
394 *
395 * If K < 1, exit from loop.
396 *
397  IF( k.LT.1 )
398  $ GO TO 100
399 *
400  kc = kc - ( n-k+1 )
401  IF( ipiv( k ).GT.0 ) THEN
402 *
403 * 1 x 1 diagonal block
404 *
405 * Multiply by inv(L**T(K)), where L(K) is the transformation
406 * stored in column K of A.
407 *
408  IF( k.LT.n )
409  $ CALL cgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
410  $ ldb, ap( kc+1 ), 1, one, b( k, 1 ), ldb )
411 *
412 * Interchange rows K and IPIV(K).
413 *
414  kp = ipiv( k )
415  IF( kp.NE.k )
416  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
417  k = k - 1
418  ELSE
419 *
420 * 2 x 2 diagonal block
421 *
422 * Multiply by inv(L**T(K-1)), where L(K-1) is the transformation
423 * stored in columns K-1 and K of A.
424 *
425  IF( k.LT.n ) THEN
426  CALL cgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
427  $ ldb, ap( kc+1 ), 1, one, b( k, 1 ), ldb )
428  CALL cgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
429  $ ldb, ap( kc-( n-k ) ), 1, one, b( k-1, 1 ),
430  $ ldb )
431  END IF
432 *
433 * Interchange rows K and -IPIV(K).
434 *
435  kp = -ipiv( k )
436  IF( kp.NE.k )
437  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
438  kc = kc - ( n-k+2 )
439  k = k - 2
440  END IF
441 *
442  GO TO 90
443  100 CONTINUE
444  END IF
445 *
446  RETURN
447 *
448 * End of CSPTRS
449 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cscal(N, CA, CX, INCX)
CSCAL
Definition: cscal.f:54
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:160
subroutine cswap(N, CX, INCX, CY, INCY)
CSWAP
Definition: cswap.f:52
subroutine cgeru(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
CGERU
Definition: cgeru.f:132
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: