LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ssytrs()

subroutine ssytrs ( character uplo,
integer n,
integer nrhs,
real, dimension( lda, * ) a,
integer lda,
integer, dimension( * ) ipiv,
real, dimension( ldb, * ) b,
integer ldb,
integer info )

SSYTRS

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

Purpose:
!>
!> SSYTRS solves a system of linear equations A*X = B with a real
!> symmetric matrix A using the factorization A = U*D*U**T or
!> A = L*D*L**T computed by SSYTRF.
!> 
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 REAL array, dimension (LDA,N)
!>          The block diagonal matrix D and the multipliers used to
!>          obtain the factor U or L as computed by SSYTRF.
!> 
[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 SSYTRF.
!> 
[in,out]B
!>          B is REAL 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.

Definition at line 117 of file ssytrs.f.

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 REAL A( LDA, * ), B( LDB, * )
130* ..
131*
132* =====================================================================
133*
134* .. Parameters ..
135 REAL ONE
136 parameter( one = 1.0e+0 )
137* ..
138* .. Local Scalars ..
139 LOGICAL UPPER
140 INTEGER J, K, KP
141 REAL AK, AKM1, AKM1K, BK, BKM1, DENOM
142* ..
143* .. External Functions ..
144 LOGICAL LSAME
145 EXTERNAL lsame
146* ..
147* .. External Subroutines ..
148 EXTERNAL sgemv, sger, sscal, sswap, 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( 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( 'SSYTRS', -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 sswap( 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 sger( k-1, nrhs, -one, a( 1, k ), 1, b( k, 1 ), ldb,
209 $ b( 1, 1 ), ldb )
210*
211* Multiply by the inverse of the diagonal block.
212*
213 CALL sscal( nrhs, one / a( k, k ), 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 sswap( 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 sger( k-2, nrhs, -one, a( 1, k ), 1, b( k, 1 ), ldb,
229 $ b( 1, 1 ), ldb )
230 CALL sger( k-2, nrhs, -one, a( 1, k-1 ), 1, b( k-1, 1 ),
231 $ ldb, b( 1, 1 ), ldb )
232*
233* Multiply by the inverse of the diagonal block.
234*
235 akm1k = a( k-1, k )
236 akm1 = a( k-1, k-1 ) / akm1k
237 ak = a( k, k ) / 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 k = k - 2
246 END IF
247*
248 GO TO 10
249 30 CONTINUE
250*
251* Next solve U**T *X = B, overwriting B with X.
252*
253* K is the main loop index, increasing from 1 to N in steps of
254* 1 or 2, depending on the size of the diagonal blocks.
255*
256 k = 1
257 40 CONTINUE
258*
259* If K > N, exit from loop.
260*
261 IF( k.GT.n )
262 $ GO TO 50
263*
264 IF( ipiv( k ).GT.0 ) THEN
265*
266* 1 x 1 diagonal block
267*
268* Multiply by inv(U**T(K)), where U(K) is the transformation
269* stored in column K of A.
270*
271 CALL sgemv( 'Transpose', k-1, nrhs, -one, b, ldb, a( 1,
272 $ k ),
273 $ 1, one, b( k, 1 ), ldb )
274*
275* Interchange rows K and IPIV(K).
276*
277 kp = ipiv( k )
278 IF( kp.NE.k )
279 $ CALL sswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
280 k = k + 1
281 ELSE
282*
283* 2 x 2 diagonal block
284*
285* Multiply by inv(U**T(K+1)), where U(K+1) is the transformation
286* stored in columns K and K+1 of A.
287*
288 CALL sgemv( 'Transpose', k-1, nrhs, -one, b, ldb, a( 1,
289 $ k ),
290 $ 1, one, b( k, 1 ), ldb )
291 CALL sgemv( '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 sswap( 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 sswap( 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 sger( 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 sscal( 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 sswap( 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 sger( n-k-1, nrhs, -one, a( k+2, k ), 1, b( k,
358 $ 1 ),
359 $ ldb, b( k+2, 1 ), ldb )
360 CALL sger( n-k-1, nrhs, -one, a( k+2, k+1 ), 1,
361 $ b( k+1, 1 ), ldb, b( k+2, 1 ), ldb )
362 END IF
363*
364* Multiply by the inverse of the diagonal block.
365*
366 akm1k = a( k+1, k )
367 akm1 = a( k, k ) / akm1k
368 ak = a( k+1, k+1 ) / akm1k
369 denom = akm1*ak - one
370 DO 70 j = 1, nrhs
371 bkm1 = b( k, j ) / akm1k
372 bk = b( k+1, j ) / akm1k
373 b( k, j ) = ( ak*bkm1-bk ) / denom
374 b( k+1, j ) = ( akm1*bk-bkm1 ) / denom
375 70 CONTINUE
376 k = k + 2
377 END IF
378*
379 GO TO 60
380 80 CONTINUE
381*
382* Next solve L**T *X = B, overwriting B with X.
383*
384* K is the main loop index, decreasing from N to 1 in steps of
385* 1 or 2, depending on the size of the diagonal blocks.
386*
387 k = n
388 90 CONTINUE
389*
390* If K < 1, exit from loop.
391*
392 IF( k.LT.1 )
393 $ GO TO 100
394*
395 IF( ipiv( k ).GT.0 ) THEN
396*
397* 1 x 1 diagonal block
398*
399* Multiply by inv(L**T(K)), where L(K) is the transformation
400* stored in column K of A.
401*
402 IF( k.LT.n )
403 $ CALL sgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
404 $ ldb, a( k+1, k ), 1, one, b( k, 1 ), ldb )
405*
406* Interchange rows K and IPIV(K).
407*
408 kp = ipiv( k )
409 IF( kp.NE.k )
410 $ CALL sswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
411 k = k - 1
412 ELSE
413*
414* 2 x 2 diagonal block
415*
416* Multiply by inv(L**T(K-1)), where L(K-1) is the transformation
417* stored in columns K-1 and K of A.
418*
419 IF( k.LT.n ) THEN
420 CALL sgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
421 $ ldb, a( k+1, k ), 1, one, b( k, 1 ), ldb )
422 CALL sgemv( 'Transpose', n-k, nrhs, -one, b( k+1, 1 ),
423 $ ldb, a( k+1, k-1 ), 1, one, b( k-1, 1 ),
424 $ ldb )
425 END IF
426*
427* Interchange rows K and -IPIV(K).
428*
429 kp = -ipiv( k )
430 IF( kp.NE.k )
431 $ CALL sswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
432 k = k - 2
433 END IF
434*
435 GO TO 90
436 100 CONTINUE
437 END IF
438*
439 RETURN
440*
441* End of SSYTRS
442*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
Definition sgemv.f:158
subroutine sger(m, n, alpha, x, incx, y, incy, a, lda)
SGER
Definition sger.f:130
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine sswap(n, sx, incx, sy, incy)
SSWAP
Definition sswap.f:82
Here is the call graph for this function:
Here is the caller graph for this function: