LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ ssytrs_aa_2stage()

subroutine ssytrs_aa_2stage ( character  UPLO,
integer  N,
integer  NRHS,
real, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  TB,
integer  LTB,
integer, dimension( * )  IPIV,
integer, dimension( * )  IPIV2,
real, dimension( ldb, * )  B,
integer  LDB,
integer  INFO 
)

SSYTRS_AA_2STAGE

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

Purpose:
 SSYTRS_AA_2STAGE solves a system of linear equations A*X = B with a real
 symmetric matrix A using the factorization A = U**T*T*U or
 A = L*T*L**T computed by SSYTRF_AA_2STAGE.
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**T*T*U;
          = 'L':  Lower triangular, form is A = L*T*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)
          Details of factors computed by SSYTRF_AA_2STAGE.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[out]TB
          TB is REAL array, dimension (LTB)
          Details of factors computed by SSYTRF_AA_2STAGE.
[in]LTB
          LTB is INTEGER
          The size of the array TB. LTB >= 4*N.
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          Details of the interchanges as computed by
          SSYTRF_AA_2STAGE.
[in]IPIV2
          IPIV2 is INTEGER array, dimension (N)
          Details of the interchanges as computed by
          SSYTRF_AA_2STAGE.
[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.
Date
November 2017

Definition at line 141 of file ssytrs_aa_2stage.f.

141 *
142 * -- LAPACK computational routine (version 3.8.0) --
143 * -- LAPACK is a software package provided by Univ. of Tennessee, --
144 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
145 * November 2017
146 *
147  IMPLICIT NONE
148 *
149 * .. Scalar Arguments ..
150  CHARACTER UPLO
151  INTEGER N, NRHS, LDA, LTB, LDB, INFO
152 * ..
153 * .. Array Arguments ..
154  INTEGER IPIV( * ), IPIV2( * )
155  REAL A( LDA, * ), TB( * ), B( LDB, * )
156 * ..
157 *
158 * =====================================================================
159 *
160  REAL ONE
161  parameter( one = 1.0e+0 )
162 * ..
163 * .. Local Scalars ..
164  INTEGER LDTB, NB
165  LOGICAL UPPER
166 * ..
167 * .. External Functions ..
168  LOGICAL LSAME
169  EXTERNAL lsame
170 * ..
171 * .. External Subroutines ..
172  EXTERNAL sgbtrs, slaswp, strsm, xerbla
173 * ..
174 * .. Intrinsic Functions ..
175  INTRINSIC max
176 * ..
177 * .. Executable Statements ..
178 *
179  info = 0
180  upper = lsame( uplo, 'U' )
181  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
182  info = -1
183  ELSE IF( n.LT.0 ) THEN
184  info = -2
185  ELSE IF( nrhs.LT.0 ) THEN
186  info = -3
187  ELSE IF( lda.LT.max( 1, n ) ) THEN
188  info = -5
189  ELSE IF( ltb.LT.( 4*n ) ) THEN
190  info = -7
191  ELSE IF( ldb.LT.max( 1, n ) ) THEN
192  info = -11
193  END IF
194  IF( info.NE.0 ) THEN
195  CALL xerbla( 'SSYTRS_AA_2STAGE', -info )
196  RETURN
197  END IF
198 *
199 * Quick return if possible
200 *
201  IF( n.EQ.0 .OR. nrhs.EQ.0 )
202  $ RETURN
203 *
204 * Read NB and compute LDTB
205 *
206  nb = int( tb( 1 ) )
207  ldtb = ltb/n
208 *
209  IF( upper ) THEN
210 *
211 * Solve A*X = B, where A = U**T*T*U.
212 *
213  IF( n.GT.nb ) THEN
214 *
215 * Pivot, P**T * B -> B
216 *
217  CALL slaswp( nrhs, b, ldb, nb+1, n, ipiv, 1 )
218 *
219 * Compute (U**T \ B) -> B [ (U**T \P**T * B) ]
220 *
221  CALL strsm( 'L', 'U', 'T', 'U', n-nb, nrhs, one, a(1, nb+1),
222  $ lda, b(nb+1, 1), ldb)
223 *
224  END IF
225 *
226 * Compute T \ B -> B [ T \ (U**T \P**T * B) ]
227 *
228  CALL sgbtrs( 'N', n, nb, nb, nrhs, tb, ldtb, ipiv2, b, ldb,
229  $ info)
230  IF( n.GT.nb ) THEN
231 *
232 * Compute (U \ B) -> B [ U \ (T \ (U**T \P**T * B) ) ]
233 *
234  CALL strsm( 'L', 'U', 'N', 'U', n-nb, nrhs, one, a(1, nb+1),
235  $ lda, b(nb+1, 1), ldb)
236 *
237 * Pivot, P * B -> B [ P * (U \ (T \ (U**T \P**T * B) )) ]
238 *
239  CALL slaswp( nrhs, b, ldb, nb+1, n, ipiv, -1 )
240 *
241  END IF
242 *
243  ELSE
244 *
245 * Solve A*X = B, where A = L*T*L**T.
246 *
247  IF( n.GT.nb ) THEN
248 *
249 * Pivot, P**T * B -> B
250 *
251  CALL slaswp( nrhs, b, ldb, nb+1, n, ipiv, 1 )
252 *
253 * Compute (L \ B) -> B [ (L \P**T * B) ]
254 *
255  CALL strsm( 'L', 'L', 'N', 'U', n-nb, nrhs, one, a(nb+1, 1),
256  $ lda, b(nb+1, 1), ldb)
257 *
258  END IF
259 *
260 * Compute T \ B -> B [ T \ (L \P**T * B) ]
261 *
262  CALL sgbtrs( 'N', n, nb, nb, nrhs, tb, ldtb, ipiv2, b, ldb,
263  $ info)
264  IF( n.GT.nb ) THEN
265 *
266 * Compute (L**T \ B) -> B [ L**T \ (T \ (L \P**T * B) ) ]
267 *
268  CALL strsm( 'L', 'L', 'T', 'U', n-nb, nrhs, one, a(nb+1, 1),
269  $ lda, b(nb+1, 1), ldb)
270 *
271 * Pivot, P * B -> B [ P * (L**T \ (T \ (L \P**T * B) )) ]
272 *
273  CALL slaswp( nrhs, b, ldb, nb+1, n, ipiv, -1 )
274 *
275  END IF
276  END IF
277 *
278  RETURN
279 *
280 * End of SSYTRS_AA_2STAGE
281 *
Here is the call graph for this function:
Here is the caller graph for this function:
sgbtrs
subroutine sgbtrs(TRANS, N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
SGBTRS
Definition: sgbtrs.f:140
slaswp
subroutine slaswp(N, A, LDA, K1, K2, IPIV, INCX)
SLASWP performs a series of row interchanges on a general rectangular matrix.
Definition: slaswp.f:117
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
strsm
subroutine strsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
STRSM
Definition: strsm.f:183
lsame
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55