LAPACK 3.12.1
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.
!>          If MIN(N,NRHS) = 0, LWORK >= 1, else LWORK >= 3*N-2.
!>
!>          If LWORK = -1, then a workspace query is assumed; the routine
!>          only calculates the minimal size of the WORK array, returns
!>          this value as the first entry of the WORK array, and no error
!>          message related to LWORK is issued by XERBLA.
!> 
[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 133 of file chetrs_aa.f.

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