LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zhetrs ( character  UPLO,
integer  N,
integer  NRHS,
complex*16, dimension( lda, * )  A,
integer  LDA,
integer, dimension( * )  IPIV,
complex*16, dimension( ldb, * )  B,
integer  LDB,
integer  INFO 
)

ZHETRS

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

Purpose:
 ZHETRS solves a system of linear equations A*X = B with a complex
 Hermitian matrix A using the factorization A = U*D*U**H or
 A = L*D*L**H computed by ZHETRF.
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**H;
          = 'L':  Lower triangular, form is A = L*D*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)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by ZHETRF.
[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 ZHETRF.
[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 2011

Definition at line 122 of file zhetrs.f.

122 *
123 * -- LAPACK computational routine (version 3.4.0) --
124 * -- LAPACK is a software package provided by Univ. of Tennessee, --
125 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126 * November 2011
127 *
128 * .. Scalar Arguments ..
129  CHARACTER uplo
130  INTEGER info, lda, ldb, n, nrhs
131 * ..
132 * .. Array Arguments ..
133  INTEGER ipiv( * )
134  COMPLEX*16 a( lda, * ), b( ldb, * )
135 * ..
136 *
137 * =====================================================================
138 *
139 * .. Parameters ..
140  COMPLEX*16 one
141  parameter ( one = ( 1.0d+0, 0.0d+0 ) )
142 * ..
143 * .. Local Scalars ..
144  LOGICAL upper
145  INTEGER j, k, kp
146  DOUBLE PRECISION s
147  COMPLEX*16 ak, akm1, akm1k, bk, bkm1, denom
148 * ..
149 * .. External Functions ..
150  LOGICAL lsame
151  EXTERNAL lsame
152 * ..
153 * .. External Subroutines ..
154  EXTERNAL xerbla, zdscal, zgemv, zgeru, zlacgv, zswap
155 * ..
156 * .. Intrinsic Functions ..
157  INTRINSIC dble, dconjg, max
158 * ..
159 * .. Executable Statements ..
160 *
161  info = 0
162  upper = lsame( uplo, 'U' )
163  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
164  info = -1
165  ELSE IF( n.LT.0 ) THEN
166  info = -2
167  ELSE IF( nrhs.LT.0 ) THEN
168  info = -3
169  ELSE IF( lda.LT.max( 1, n ) ) THEN
170  info = -5
171  ELSE IF( ldb.LT.max( 1, n ) ) THEN
172  info = -8
173  END IF
174  IF( info.NE.0 ) THEN
175  CALL xerbla( 'ZHETRS', -info )
176  RETURN
177  END IF
178 *
179 * Quick return if possible
180 *
181  IF( n.EQ.0 .OR. nrhs.EQ.0 )
182  $ RETURN
183 *
184  IF( upper ) THEN
185 *
186 * Solve A*X = B, where A = U*D*U**H.
187 *
188 * First solve U*D*X = B, overwriting B with X.
189 *
190 * K is the main loop index, decreasing from N to 1 in steps of
191 * 1 or 2, depending on the size of the diagonal blocks.
192 *
193  k = n
194  10 CONTINUE
195 *
196 * If K < 1, exit from loop.
197 *
198  IF( k.LT.1 )
199  $ GO TO 30
200 *
201  IF( ipiv( k ).GT.0 ) THEN
202 *
203 * 1 x 1 diagonal block
204 *
205 * Interchange rows K and IPIV(K).
206 *
207  kp = ipiv( k )
208  IF( kp.NE.k )
209  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
210 *
211 * Multiply by inv(U(K)), where U(K) is the transformation
212 * stored in column K of A.
213 *
214  CALL zgeru( k-1, nrhs, -one, a( 1, k ), 1, b( k, 1 ), ldb,
215  $ b( 1, 1 ), ldb )
216 *
217 * Multiply by the inverse of the diagonal block.
218 *
219  s = dble( one ) / dble( a( k, k ) )
220  CALL zdscal( nrhs, s, b( k, 1 ), ldb )
221  k = k - 1
222  ELSE
223 *
224 * 2 x 2 diagonal block
225 *
226 * Interchange rows K-1 and -IPIV(K).
227 *
228  kp = -ipiv( k )
229  IF( kp.NE.k-1 )
230  $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
231 *
232 * Multiply by inv(U(K)), where U(K) is the transformation
233 * stored in columns K-1 and K of A.
234 *
235  CALL zgeru( k-2, nrhs, -one, a( 1, k ), 1, b( k, 1 ), ldb,
236  $ b( 1, 1 ), ldb )
237  CALL zgeru( k-2, nrhs, -one, a( 1, k-1 ), 1, b( k-1, 1 ),
238  $ ldb, b( 1, 1 ), ldb )
239 *
240 * Multiply by the inverse of the diagonal block.
241 *
242  akm1k = a( k-1, k )
243  akm1 = a( k-1, k-1 ) / akm1k
244  ak = a( k, k ) / dconjg( akm1k )
245  denom = akm1*ak - one
246  DO 20 j = 1, nrhs
247  bkm1 = b( k-1, j ) / akm1k
248  bk = b( k, j ) / dconjg( akm1k )
249  b( k-1, j ) = ( ak*bkm1-bk ) / denom
250  b( k, j ) = ( akm1*bk-bkm1 ) / denom
251  20 CONTINUE
252  k = k - 2
253  END IF
254 *
255  GO TO 10
256  30 CONTINUE
257 *
258 * Next solve U**H *X = B, overwriting B with X.
259 *
260 * K is the main loop index, increasing from 1 to N in steps of
261 * 1 or 2, depending on the size of the diagonal blocks.
262 *
263  k = 1
264  40 CONTINUE
265 *
266 * If K > N, exit from loop.
267 *
268  IF( k.GT.n )
269  $ GO TO 50
270 *
271  IF( ipiv( k ).GT.0 ) THEN
272 *
273 * 1 x 1 diagonal block
274 *
275 * Multiply by inv(U**H(K)), where U(K) is the transformation
276 * stored in column K of A.
277 *
278  IF( k.GT.1 ) THEN
279  CALL zlacgv( nrhs, b( k, 1 ), ldb )
280  CALL zgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
281  $ ldb, a( 1, k ), 1, one, b( k, 1 ), ldb )
282  CALL zlacgv( nrhs, b( k, 1 ), ldb )
283  END IF
284 *
285 * Interchange rows K and IPIV(K).
286 *
287  kp = ipiv( k )
288  IF( kp.NE.k )
289  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
290  k = k + 1
291  ELSE
292 *
293 * 2 x 2 diagonal block
294 *
295 * Multiply by inv(U**H(K+1)), where U(K+1) is the transformation
296 * stored in columns K and K+1 of A.
297 *
298  IF( k.GT.1 ) THEN
299  CALL zlacgv( nrhs, b( k, 1 ), ldb )
300  CALL zgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
301  $ ldb, a( 1, k ), 1, one, b( k, 1 ), ldb )
302  CALL zlacgv( nrhs, b( k, 1 ), ldb )
303 *
304  CALL zlacgv( nrhs, b( k+1, 1 ), ldb )
305  CALL zgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
306  $ ldb, a( 1, k+1 ), 1, one, b( k+1, 1 ), ldb )
307  CALL zlacgv( nrhs, b( k+1, 1 ), ldb )
308  END IF
309 *
310 * Interchange rows K and -IPIV(K).
311 *
312  kp = -ipiv( k )
313  IF( kp.NE.k )
314  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
315  k = k + 2
316  END IF
317 *
318  GO TO 40
319  50 CONTINUE
320 *
321  ELSE
322 *
323 * Solve A*X = B, where A = L*D*L**H.
324 *
325 * First solve L*D*X = B, overwriting B with X.
326 *
327 * K is the main loop index, increasing from 1 to N in steps of
328 * 1 or 2, depending on the size of the diagonal blocks.
329 *
330  k = 1
331  60 CONTINUE
332 *
333 * If K > N, exit from loop.
334 *
335  IF( k.GT.n )
336  $ GO TO 80
337 *
338  IF( ipiv( k ).GT.0 ) THEN
339 *
340 * 1 x 1 diagonal block
341 *
342 * Interchange rows K and IPIV(K).
343 *
344  kp = ipiv( k )
345  IF( kp.NE.k )
346  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
347 *
348 * Multiply by inv(L(K)), where L(K) is the transformation
349 * stored in column K of A.
350 *
351  IF( k.LT.n )
352  $ CALL zgeru( n-k, nrhs, -one, a( k+1, k ), 1, b( k, 1 ),
353  $ ldb, b( k+1, 1 ), ldb )
354 *
355 * Multiply by the inverse of the diagonal block.
356 *
357  s = dble( one ) / dble( a( k, k ) )
358  CALL zdscal( nrhs, s, b( k, 1 ), ldb )
359  k = k + 1
360  ELSE
361 *
362 * 2 x 2 diagonal block
363 *
364 * Interchange rows K+1 and -IPIV(K).
365 *
366  kp = -ipiv( k )
367  IF( kp.NE.k+1 )
368  $ CALL zswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ), ldb )
369 *
370 * Multiply by inv(L(K)), where L(K) is the transformation
371 * stored in columns K and K+1 of A.
372 *
373  IF( k.LT.n-1 ) THEN
374  CALL zgeru( n-k-1, nrhs, -one, a( k+2, k ), 1, b( k, 1 ),
375  $ ldb, b( k+2, 1 ), ldb )
376  CALL zgeru( n-k-1, nrhs, -one, a( k+2, k+1 ), 1,
377  $ b( k+1, 1 ), ldb, b( k+2, 1 ), ldb )
378  END IF
379 *
380 * Multiply by the inverse of the diagonal block.
381 *
382  akm1k = a( k+1, k )
383  akm1 = a( k, k ) / dconjg( akm1k )
384  ak = a( k+1, k+1 ) / akm1k
385  denom = akm1*ak - one
386  DO 70 j = 1, nrhs
387  bkm1 = b( k, j ) / dconjg( akm1k )
388  bk = b( k+1, j ) / akm1k
389  b( k, j ) = ( ak*bkm1-bk ) / denom
390  b( k+1, j ) = ( akm1*bk-bkm1 ) / denom
391  70 CONTINUE
392  k = k + 2
393  END IF
394 *
395  GO TO 60
396  80 CONTINUE
397 *
398 * Next solve L**H *X = B, overwriting B with X.
399 *
400 * K is the main loop index, decreasing from N to 1 in steps of
401 * 1 or 2, depending on the size of the diagonal blocks.
402 *
403  k = n
404  90 CONTINUE
405 *
406 * If K < 1, exit from loop.
407 *
408  IF( k.LT.1 )
409  $ GO TO 100
410 *
411  IF( ipiv( k ).GT.0 ) THEN
412 *
413 * 1 x 1 diagonal block
414 *
415 * Multiply by inv(L**H(K)), where L(K) is the transformation
416 * stored in column K of A.
417 *
418  IF( k.LT.n ) THEN
419  CALL zlacgv( nrhs, b( k, 1 ), ldb )
420  CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
421  $ b( k+1, 1 ), ldb, a( k+1, k ), 1, one,
422  $ b( k, 1 ), ldb )
423  CALL zlacgv( nrhs, b( k, 1 ), ldb )
424  END IF
425 *
426 * Interchange rows K and IPIV(K).
427 *
428  kp = ipiv( k )
429  IF( kp.NE.k )
430  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
431  k = k - 1
432  ELSE
433 *
434 * 2 x 2 diagonal block
435 *
436 * Multiply by inv(L**H(K-1)), where L(K-1) is the transformation
437 * stored in columns K-1 and K of A.
438 *
439  IF( k.LT.n ) THEN
440  CALL zlacgv( nrhs, b( k, 1 ), ldb )
441  CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
442  $ b( k+1, 1 ), ldb, a( k+1, k ), 1, one,
443  $ b( k, 1 ), ldb )
444  CALL zlacgv( nrhs, b( k, 1 ), ldb )
445 *
446  CALL zlacgv( nrhs, b( k-1, 1 ), ldb )
447  CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
448  $ b( k+1, 1 ), ldb, a( k+1, k-1 ), 1, one,
449  $ b( k-1, 1 ), ldb )
450  CALL zlacgv( nrhs, b( k-1, 1 ), ldb )
451  END IF
452 *
453 * Interchange rows K and -IPIV(K).
454 *
455  kp = -ipiv( k )
456  IF( kp.NE.k )
457  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
458  k = k - 2
459  END IF
460 *
461  GO TO 90
462  100 CONTINUE
463  END IF
464 *
465  RETURN
466 *
467 * End of ZHETRS
468 *
subroutine zgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
ZGEMV
Definition: zgemv.f:160
subroutine zswap(N, ZX, INCX, ZY, INCY)
ZSWAP
Definition: zswap.f:52
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zdscal(N, DA, ZX, INCX)
ZDSCAL
Definition: zdscal.f:54
subroutine zgeru(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
ZGERU
Definition: zgeru.f:132
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine zlacgv(N, X, INCX)
ZLACGV conjugates a complex vector.
Definition: zlacgv.f:76

Here is the call graph for this function:

Here is the caller graph for this function: