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

◆ csyconvf()

subroutine csyconvf ( character uplo,
character way,
integer n,
complex, dimension( lda, * ) a,
integer lda,
complex, dimension( * ) e,
integer, dimension( * ) ipiv,
integer info )

CSYCONVF

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

Purpose:
!> If parameter WAY = 'C':
!> CSYCONVF converts the factorization output format used in
!> CSYTRF provided on entry in parameter A into the factorization
!> output format used in CSYTRF_RK (or CSYTRF_BK) that is stored
!> on exit in parameters A and E. It also converts in place details of
!> the interchanges stored in IPIV from the format used in CSYTRF into
!> the format used in CSYTRF_RK (or CSYTRF_BK).
!>
!> If parameter WAY = 'R':
!> CSYCONVF performs the conversion in reverse direction, i.e.
!> converts the factorization output format used in CSYTRF_RK
!> (or CSYTRF_BK) provided on entry in parameters A and E into
!> the factorization output format used in CSYTRF that is stored
!> on exit in parameter A. It also converts in place details of
!> the interchanges stored in IPIV from the format used in CSYTRF_RK
!> (or CSYTRF_BK) into the format used in CSYTRF.
!>
!> CSYCONVF can also convert in Hermitian matrix case, i.e. between
!> formats used in CHETRF and CHETRF_RK (or CHETRF_BK).
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          Specifies whether the details of the factorization are
!>          stored as an upper or lower triangular matrix A.
!>          = 'U':  Upper triangular
!>          = 'L':  Lower triangular
!> 
[in]WAY
!>          WAY is CHARACTER*1
!>          = 'C': Convert
!>          = 'R': Revert
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in,out]A
!>          A is COMPLEX array, dimension (LDA,N)
!>
!>          1) If WAY ='C':
!>
!>          On entry, contains factorization details in format used in
!>          CSYTRF:
!>            a) all elements of the symmetric block diagonal
!>               matrix D on the diagonal of A and on superdiagonal
!>               (or subdiagonal) of A, and
!>            b) If UPLO = 'U': multipliers used to obtain factor U
!>               in the superdiagonal part of A.
!>               If UPLO = 'L': multipliers used to obtain factor L
!>               in the superdiagonal part of A.
!>
!>          On exit, contains factorization details in format used in
!>          CSYTRF_RK or CSYTRF_BK:
!>            a) ONLY diagonal elements of the symmetric block diagonal
!>               matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
!>               (superdiagonal (or subdiagonal) elements of D
!>                are stored on exit in array E), and
!>            b) If UPLO = 'U': factor U in the superdiagonal part of A.
!>               If UPLO = 'L': factor L in the subdiagonal part of A.
!>
!>          2) If WAY = 'R':
!>
!>          On entry, contains factorization details in format used in
!>          CSYTRF_RK or CSYTRF_BK:
!>            a) ONLY diagonal elements of the symmetric block diagonal
!>               matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
!>               (superdiagonal (or subdiagonal) elements of D
!>                are stored on exit in array E), and
!>            b) If UPLO = 'U': factor U in the superdiagonal part of A.
!>               If UPLO = 'L': factor L in the subdiagonal part of A.
!>
!>          On exit, contains factorization details in format used in
!>          CSYTRF:
!>            a) all elements of the symmetric block diagonal
!>               matrix D on the diagonal of A and on superdiagonal
!>               (or subdiagonal) of A, and
!>            b) If UPLO = 'U': multipliers used to obtain factor U
!>               in the superdiagonal part of A.
!>               If UPLO = 'L': multipliers used to obtain factor L
!>               in the superdiagonal part of A.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in,out]E
!>          E is COMPLEX array, dimension (N)
!>
!>          1) If WAY ='C':
!>
!>          On entry, just a workspace.
!>
!>          On exit, contains the superdiagonal (or subdiagonal)
!>          elements of the symmetric block diagonal matrix D
!>          with 1-by-1 or 2-by-2 diagonal blocks, where
!>          If UPLO = 'U': E(i) = D(i-1,i), i=2:N, E(1) is set to 0;
!>          If UPLO = 'L': E(i) = D(i+1,i), i=1:N-1, E(N) is set to 0.
!>
!>          2) If WAY = 'R':
!>
!>          On entry, contains the superdiagonal (or subdiagonal)
!>          elements of the symmetric block diagonal matrix D
!>          with 1-by-1 or 2-by-2 diagonal blocks, where
!>          If UPLO = 'U': E(i) = D(i-1,i),i=2:N, E(1) not referenced;
!>          If UPLO = 'L': E(i) = D(i+1,i),i=1:N-1, E(N) not referenced.
!>
!>          On exit, is not changed
!> 
[in,out]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>
!>          1) If WAY ='C':
!>          On entry, details of the interchanges and the block
!>          structure of D in the format used in CSYTRF.
!>          On exit, details of the interchanges and the block
!>          structure of D in the format used in CSYTRF_RK
!>          ( or CSYTRF_BK).
!>
!>          1) If WAY ='R':
!>          On entry, details of the interchanges and the block
!>          structure of D in the format used in CSYTRF_RK
!>          ( or CSYTRF_BK).
!>          On exit, details of the interchanges and the block
!>          structure of D in the format used in CSYTRF.
!> 
[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.
Contributors:
!>
!>  November 2017,  Igor Kozachenko,
!>                  Computer Science Division,
!>                  University of California, Berkeley
!>
!> 

Definition at line 206 of file csyconvf.f.

207*
208* -- LAPACK computational routine --
209* -- LAPACK is a software package provided by Univ. of Tennessee, --
210* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
211*
212* .. Scalar Arguments ..
213 CHARACTER UPLO, WAY
214 INTEGER INFO, LDA, N
215* ..
216* .. Array Arguments ..
217 INTEGER IPIV( * )
218 COMPLEX A( LDA, * ), E( * )
219* ..
220*
221* =====================================================================
222*
223* .. Parameters ..
224 COMPLEX ZERO
225 parameter( zero = ( 0.0e+0, 0.0e+0 ) )
226* ..
227* .. External Functions ..
228 LOGICAL LSAME
229 EXTERNAL lsame
230*
231* .. External Subroutines ..
232 EXTERNAL cswap, xerbla
233* .. Local Scalars ..
234 LOGICAL UPPER, CONVERT
235 INTEGER I, IP
236* ..
237* .. Executable Statements ..
238*
239 info = 0
240 upper = lsame( uplo, 'U' )
241 convert = lsame( way, 'C' )
242 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
243 info = -1
244 ELSE IF( .NOT.convert .AND. .NOT.lsame( way, 'R' ) ) THEN
245 info = -2
246 ELSE IF( n.LT.0 ) THEN
247 info = -3
248 ELSE IF( lda.LT.max( 1, n ) ) THEN
249 info = -5
250
251 END IF
252 IF( info.NE.0 ) THEN
253 CALL xerbla( 'CSYCONVF', -info )
254 RETURN
255 END IF
256*
257* Quick return if possible
258*
259 IF( n.EQ.0 )
260 $ RETURN
261*
262 IF( upper ) THEN
263*
264* Begin A is UPPER
265*
266 IF ( convert ) THEN
267*
268* Convert A (A is upper)
269*
270*
271* Convert VALUE
272*
273* Assign superdiagonal entries of D to array E and zero out
274* corresponding entries in input storage A
275*
276 i = n
277 e( 1 ) = zero
278 DO WHILE ( i.GT.1 )
279 IF( ipiv( i ).LT.0 ) THEN
280 e( i ) = a( i-1, i )
281 e( i-1 ) = zero
282 a( i-1, i ) = zero
283 i = i - 1
284 ELSE
285 e( i ) = zero
286 END IF
287 i = i - 1
288 END DO
289*
290* Convert PERMUTATIONS and IPIV
291*
292* Apply permutations to submatrices of upper part of A
293* in factorization order where i decreases from N to 1
294*
295 i = n
296 DO WHILE ( i.GE.1 )
297 IF( ipiv( i ).GT.0 ) THEN
298*
299* 1-by-1 pivot interchange
300*
301* Swap rows i and IPIV(i) in A(1:i,N-i:N)
302*
303 ip = ipiv( i )
304 IF( i.LT.n ) THEN
305 IF( ip.NE.i ) THEN
306 CALL cswap( n-i, a( i, i+1 ), lda,
307 $ a( ip, i+1 ), lda )
308 END IF
309 END IF
310*
311 ELSE
312*
313* 2-by-2 pivot interchange
314*
315* Swap rows i-1 and IPIV(i) in A(1:i,N-i:N)
316*
317 ip = -ipiv( i )
318 IF( i.LT.n ) THEN
319 IF( ip.NE.(i-1) ) THEN
320 CALL cswap( n-i, a( i-1, i+1 ), lda,
321 $ a( ip, i+1 ), lda )
322 END IF
323 END IF
324*
325* Convert IPIV
326* There is no interchange of rows i and and IPIV(i),
327* so this should be reflected in IPIV format for
328* *SYTRF_RK ( or *SYTRF_BK)
329*
330 ipiv( i ) = i
331*
332 i = i - 1
333*
334 END IF
335 i = i - 1
336 END DO
337*
338 ELSE
339*
340* Revert A (A is upper)
341*
342*
343* Revert PERMUTATIONS and IPIV
344*
345* Apply permutations to submatrices of upper part of A
346* in reverse factorization order where i increases from 1 to N
347*
348 i = 1
349 DO WHILE ( i.LE.n )
350 IF( ipiv( i ).GT.0 ) THEN
351*
352* 1-by-1 pivot interchange
353*
354* Swap rows i and IPIV(i) in A(1:i,N-i:N)
355*
356 ip = ipiv( i )
357 IF( i.LT.n ) THEN
358 IF( ip.NE.i ) THEN
359 CALL cswap( n-i, a( ip, i+1 ), lda,
360 $ a( i, i+1 ), lda )
361 END IF
362 END IF
363*
364 ELSE
365*
366* 2-by-2 pivot interchange
367*
368* Swap rows i-1 and IPIV(i) in A(1:i,N-i:N)
369*
370 i = i + 1
371 ip = -ipiv( i )
372 IF( i.LT.n ) THEN
373 IF( ip.NE.(i-1) ) THEN
374 CALL cswap( n-i, a( ip, i+1 ), lda,
375 $ a( i-1, i+1 ), lda )
376 END IF
377 END IF
378*
379* Convert IPIV
380* There is one interchange of rows i-1 and IPIV(i-1),
381* so this should be recorded in two consecutive entries
382* in IPIV format for *SYTRF
383*
384 ipiv( i ) = ipiv( i-1 )
385*
386 END IF
387 i = i + 1
388 END DO
389*
390* Revert VALUE
391* Assign superdiagonal entries of D from array E to
392* superdiagonal entries of A.
393*
394 i = n
395 DO WHILE ( i.GT.1 )
396 IF( ipiv( i ).LT.0 ) THEN
397 a( i-1, i ) = e( i )
398 i = i - 1
399 END IF
400 i = i - 1
401 END DO
402*
403* End A is UPPER
404*
405 END IF
406*
407 ELSE
408*
409* Begin A is LOWER
410*
411 IF ( convert ) THEN
412*
413* Convert A (A is lower)
414*
415*
416* Convert VALUE
417* Assign subdiagonal entries of D to array E and zero out
418* corresponding entries in input storage A
419*
420 i = 1
421 e( n ) = zero
422 DO WHILE ( i.LE.n )
423 IF( i.LT.n .AND. ipiv(i).LT.0 ) THEN
424 e( i ) = a( i+1, i )
425 e( i+1 ) = zero
426 a( i+1, i ) = zero
427 i = i + 1
428 ELSE
429 e( i ) = zero
430 END IF
431 i = i + 1
432 END DO
433*
434* Convert PERMUTATIONS and IPIV
435*
436* Apply permutations to submatrices of lower part of A
437* in factorization order where k increases from 1 to N
438*
439 i = 1
440 DO WHILE ( i.LE.n )
441 IF( ipiv( i ).GT.0 ) THEN
442*
443* 1-by-1 pivot interchange
444*
445* Swap rows i and IPIV(i) in A(i:N,1:i-1)
446*
447 ip = ipiv( i )
448 IF ( i.GT.1 ) THEN
449 IF( ip.NE.i ) THEN
450 CALL cswap( i-1, a( i, 1 ), lda,
451 $ a( ip, 1 ), lda )
452 END IF
453 END IF
454*
455 ELSE
456*
457* 2-by-2 pivot interchange
458*
459* Swap rows i+1 and IPIV(i) in A(i:N,1:i-1)
460*
461 ip = -ipiv( i )
462 IF ( i.GT.1 ) THEN
463 IF( ip.NE.(i+1) ) THEN
464 CALL cswap( i-1, a( i+1, 1 ), lda,
465 $ a( ip, 1 ), lda )
466 END IF
467 END IF
468*
469* Convert IPIV
470* There is no interchange of rows i and and IPIV(i),
471* so this should be reflected in IPIV format for
472* *SYTRF_RK ( or *SYTRF_BK)
473*
474 ipiv( i ) = i
475*
476 i = i + 1
477*
478 END IF
479 i = i + 1
480 END DO
481*
482 ELSE
483*
484* Revert A (A is lower)
485*
486*
487* Revert PERMUTATIONS and IPIV
488*
489* Apply permutations to submatrices of lower part of A
490* in reverse factorization order where i decreases from N to 1
491*
492 i = n
493 DO WHILE ( i.GE.1 )
494 IF( ipiv( i ).GT.0 ) THEN
495*
496* 1-by-1 pivot interchange
497*
498* Swap rows i and IPIV(i) in A(i:N,1:i-1)
499*
500 ip = ipiv( i )
501 IF ( i.GT.1 ) THEN
502 IF( ip.NE.i ) THEN
503 CALL cswap( i-1, a( ip, 1 ), lda,
504 $ a( i, 1 ), lda )
505 END IF
506 END IF
507*
508 ELSE
509*
510* 2-by-2 pivot interchange
511*
512* Swap rows i+1 and IPIV(i) in A(i:N,1:i-1)
513*
514 i = i - 1
515 ip = -ipiv( i )
516 IF ( i.GT.1 ) THEN
517 IF( ip.NE.(i+1) ) THEN
518 CALL cswap( i-1, a( ip, 1 ), lda,
519 $ a( i+1, 1 ), lda )
520 END IF
521 END IF
522*
523* Convert IPIV
524* There is one interchange of rows i+1 and IPIV(i+1),
525* so this should be recorded in consecutive entries
526* in IPIV format for *SYTRF
527*
528 ipiv( i ) = ipiv( i+1 )
529*
530 END IF
531 i = i - 1
532 END DO
533*
534* Revert VALUE
535* Assign subdiagonal entries of D from array E to
536* subdiagonal entries of A.
537*
538 i = 1
539 DO WHILE ( i.LE.n-1 )
540 IF( ipiv( i ).LT.0 ) THEN
541 a( i + 1, i ) = e( i )
542 i = i + 1
543 END IF
544 i = i + 1
545 END DO
546*
547 END IF
548*
549* End A is LOWER
550*
551 END IF
552
553 RETURN
554*
555* End of CSYCONVF
556*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81
Here is the call graph for this function: