LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ zhetrs_aa_2stage()

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

ZHETRS_AA_2STAGE

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

Purpose:
 ZHETRS_AA_2STAGE solves a system of linear equations A*X = B with a 
 hermitian matrix A using the factorization A = U**H*T*U or
 A = L*T*L**H computed by ZHETRF_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**H*T*U;
          = 'L':  Lower triangular, form is A = L*T*L**H.
[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)
          Details of factors computed by ZHETRF_AA_2STAGE.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[out]TB
          TB is COMPLEX*16 array, dimension (LTB)
          Details of factors computed by ZHETRF_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
          ZHETRF_AA_2STAGE.
[in]IPIV2
          IPIV2 is INTEGER array, dimension (N)
          Details of the interchanges as computed by
          ZHETRF_AA_2STAGE.
[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 2017

Definition at line 143 of file zhetrs_aa_2stage.f.

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