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

◆ chetrs_aa()

subroutine chetrs_aa ( 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  lwork,
integer  info 
)

CHETRS_AA

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

Purpose:
 CHETRS_AA solves a system of linear equations A*X = B with a complex
 hermitian matrix A using the factorization A = U**H*T*U or
 A = L*T*L**H computed by CHETRF_AA.
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 array, dimension (LDA,N)
          Details of factors computed by CHETRF_AA.
[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 as computed by CHETRF_AA.
[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 (MAX(1,LWORK))
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK. LWORK >= max(1,3*N-2).
[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 129 of file chetrs_aa.f.

131*
132* -- LAPACK computational routine --
133* -- LAPACK is a software package provided by Univ. of Tennessee, --
134* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
135*
136 IMPLICIT NONE
137*
138* .. Scalar Arguments ..
139 CHARACTER UPLO
140 INTEGER N, NRHS, LDA, LDB, LWORK, INFO
141* ..
142* .. Array Arguments ..
143 INTEGER IPIV( * )
144 COMPLEX A( LDA, * ), B( LDB, * ), WORK( * )
145* ..
146*
147* =====================================================================
148*
149 COMPLEX ONE
150 parameter( one = 1.0e+0 )
151* ..
152* .. Local Scalars ..
153 LOGICAL LQUERY, UPPER
154 INTEGER K, KP, LWKOPT
155* ..
156* .. External Functions ..
157 LOGICAL LSAME
158 REAL SROUNDUP_LWORK
159 EXTERNAL lsame,sroundup_lwork
160* ..
161* .. External Subroutines ..
162 EXTERNAL clacpy, clacgv, cgtsv, cswap, ctrsm, xerbla
163* ..
164* .. Intrinsic Functions ..
165 INTRINSIC max
166* ..
167* .. Executable Statements ..
168*
169 info = 0
170 upper = lsame( uplo, 'U' )
171 lquery = ( lwork.EQ.-1 )
172 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
173 info = -1
174 ELSE IF( n.LT.0 ) THEN
175 info = -2
176 ELSE IF( nrhs.LT.0 ) THEN
177 info = -3
178 ELSE IF( lda.LT.max( 1, n ) ) THEN
179 info = -5
180 ELSE IF( ldb.LT.max( 1, n ) ) THEN
181 info = -8
182 ELSE IF( lwork.LT.max( 1, 3*n-2 ) .AND. .NOT.lquery ) THEN
183 info = -10
184 END IF
185 IF( info.NE.0 ) THEN
186 CALL xerbla( 'CHETRS_AA', -info )
187 RETURN
188 ELSE IF( lquery ) THEN
189 lwkopt = (3*n-2)
190 work( 1 ) = sroundup_lwork(lwkopt)
191 RETURN
192 END IF
193*
194* Quick return if possible
195*
196 IF( n.EQ.0 .OR. nrhs.EQ.0 )
197 $ RETURN
198*
199 IF( upper ) THEN
200*
201* Solve A*X = B, where A = U**H*T*U.
202*
203* 1) Forward substitution with U**H
204*
205 IF( n.GT.1 ) THEN
206*
207* Pivot, P**T * B -> B
208*
209 k = 1
210 DO WHILE ( k.LE.n )
211 kp = ipiv( k )
212 IF( kp.NE.k )
213 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
214 k = k + 1
215 END DO
216*
217* Compute U**H \ B -> B [ (U**H \P**T * B) ]
218*
219 CALL ctrsm( 'L', 'U', 'C', 'U', n-1, nrhs, one, a( 1, 2 ),
220 $ lda, b( 2, 1 ), ldb)
221 END IF
222*
223* 2) Solve with triangular matrix T
224*
225* Compute T \ B -> B [ T \ (U**H \P**T * B) ]
226*
227 CALL clacpy( 'F', 1, n, a(1, 1), lda+1, work(n), 1)
228 IF( n.GT.1 ) THEN
229 CALL clacpy( 'F', 1, n-1, a( 1, 2 ), lda+1, work( 2*n ), 1)
230 CALL clacpy( 'F', 1, n-1, a( 1, 2 ), lda+1, work( 1 ), 1)
231 CALL clacgv( n-1, work( 1 ), 1 )
232 END IF
233 CALL cgtsv(n, nrhs, work(1), work(n), work(2*n), b, ldb,
234 $ info)
235*
236* 3) Backward substitution with U
237*
238 IF( n.GT.1 ) THEN
239*
240* Compute U \ B -> B [ U \ (T \ (U**H \P**T * B) ) ]
241*
242 CALL ctrsm( 'L', 'U', 'N', 'U', n-1, nrhs, one, a( 1, 2 ),
243 $ lda, b(2, 1), ldb)
244*
245* Pivot, P * B -> B [ P * (U \ (T \ (U**H \P**T * B) )) ]
246*
247 k = n
248 DO WHILE ( k.GE.1 )
249 kp = ipiv( k )
250 IF( kp.NE.k )
251 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
252 k = k - 1
253 END DO
254 END IF
255*
256 ELSE
257*
258* Solve A*X = B, where A = L*T*L**H.
259*
260* 1) Forward substitution with L
261*
262 IF( n.GT.1 ) THEN
263*
264* Pivot, P**T * B -> B
265*
266 k = 1
267 DO WHILE ( k.LE.n )
268 kp = ipiv( k )
269 IF( kp.NE.k )
270 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
271 k = k + 1
272 END DO
273*
274* Compute L \ B -> B [ (L \P**T * B) ]
275*
276 CALL ctrsm( 'L', 'L', 'N', 'U', n-1, nrhs, one, a( 2, 1),
277 $ lda, b(2, 1), ldb )
278 END IF
279*
280* 2) Solve with triangular matrix T
281*
282* Compute T \ B -> B [ T \ (L \P**T * B) ]
283*
284 CALL clacpy( 'F', 1, n, a(1, 1), lda+1, work(n), 1)
285 IF( n.GT.1 ) THEN
286 CALL clacpy( 'F', 1, n-1, a( 2, 1 ), lda+1, work( 1 ), 1 )
287 CALL clacpy( 'F', 1, n-1, a( 2, 1 ), lda+1, work( 2*n ), 1)
288 CALL clacgv( n-1, work( 2*n ), 1 )
289 END IF
290 CALL cgtsv(n, nrhs, work(1), work(n), work(2*n), b, ldb,
291 $ info)
292*
293* 3) Backward substitution with L**H
294*
295 IF( n.GT.1 ) THEN
296*
297* Compute (L**H \ B) -> B [ L**H \ (T \ (L \P**T * B) ) ]
298*
299 CALL ctrsm( 'L', 'L', 'C', 'U', n-1, nrhs, one, a( 2, 1 ),
300 $ lda, b( 2, 1 ), ldb )
301*
302* Pivot, P * B -> B [ P * (L**H \ (T \ (L \P**T * B) )) ]
303*
304 k = n
305 DO WHILE ( k.GE.1 )
306 kp = ipiv( k )
307 IF( kp.NE.k )
308 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
309 k = k - 1
310 END DO
311 END IF
312*
313 END IF
314*
315 RETURN
316*
317* End of CHETRS_AA
318*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgtsv(n, nrhs, dl, d, du, b, ldb, info)
CGTSV computes the solution to system of linear equations A * X = B for GT matrices
Definition cgtsv.f:124
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:74
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
Definition clacpy.f:103
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81
subroutine ctrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
CTRSM
Definition ctrsm.f:180
Here is the call graph for this function:
Here is the caller graph for this function: