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

◆ dsyconvf_rook()

subroutine dsyconvf_rook ( character  uplo,
character  way,
integer  n,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( * )  e,
integer, dimension( * )  ipiv,
integer  info 
)

DSYCONVF_ROOK

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

Purpose:
 If parameter WAY = 'C':
 DSYCONVF_ROOK converts the factorization output format used in
 DSYTRF_ROOK provided on entry in parameter A into the factorization
 output format used in DSYTRF_RK (or DSYTRF_BK) that is stored
 on exit in parameters A and E. IPIV format for DSYTRF_ROOK and
 DSYTRF_RK (or DSYTRF_BK) is the same and is not converted.

 If parameter WAY = 'R':
 DSYCONVF_ROOK performs the conversion in reverse direction, i.e.
 converts the factorization output format used in DSYTRF_RK
 (or DSYTRF_BK) provided on entry in parameters A and E into
 the factorization output format used in DSYTRF_ROOK that is stored
 on exit in parameter A. IPIV format for DSYTRF_ROOK and
 DSYTRF_RK (or DSYTRF_BK) is the same and is not converted.
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 DOUBLE PRECISION array, dimension (LDA,N)

          1) If WAY ='C':

          On entry, contains factorization details in format used in
          DSYTRF_ROOK:
            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
          DSYTRF_RK or DSYTRF_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
          DSYTRF_RK or DSYTRF_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
          DSYTRF_ROOK:
            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 DOUBLE PRECISION 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]IPIV
          IPIV is INTEGER array, dimension (N)
          On entry, details of the interchanges and the block
          structure of D as determined:
          1) by DSYTRF_ROOK, if WAY ='C';
          2) by DSYTRF_RK (or DSYTRF_BK), if WAY ='R'.
          The IPIV format is the same for all these routines.

          On exit, is not changed.
[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 196 of file dsyconvf_rook.f.

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