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

◆ ztrttf()

subroutine ztrttf ( character transr,
character uplo,
integer n,
complex*16, dimension( 0: lda-1, 0: * ) a,
integer lda,
complex*16, dimension( 0: * ) arf,
integer info )

ZTRTTF copies a triangular matrix from the standard full format (TR) to the rectangular full packed format (TF).

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

Purpose:
!>
!> ZTRTTF copies a triangular matrix A from standard full format (TR)
!> to rectangular full packed format (TF) .
!> 
Parameters
[in]TRANSR
!>          TRANSR is CHARACTER*1
!>          = 'N':  ARF in Normal mode is wanted;
!>          = 'C':  ARF in Conjugate Transpose mode is wanted;
!> 
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  A is upper triangular;
!>          = 'L':  A is lower triangular.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension ( LDA, N )
!>          On entry, the triangular matrix A.  If UPLO = 'U', the
!>          leading N-by-N upper triangular part of the array A contains
!>          the upper triangular matrix, and the strictly lower
!>          triangular part of A is not referenced.  If UPLO = 'L', the
!>          leading N-by-N lower triangular part of the array A contains
!>          the lower triangular matrix, and the strictly upper
!>          triangular part of A is not referenced.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the matrix A.  LDA >= max(1,N).
!> 
[out]ARF
!>          ARF is COMPLEX*16 array, dimension ( N*(N+1)/2 ),
!>          On exit, the upper or lower triangular matrix A stored in
!>          RFP format. For a further discussion see Notes below.
!> 
[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.
Further Details:
!>
!>  We first consider Standard Packed Format when N is even.
!>  We give an example where N = 6.
!>
!>      AP is Upper             AP is Lower
!>
!>   00 01 02 03 04 05       00
!>      11 12 13 14 15       10 11
!>         22 23 24 25       20 21 22
!>            33 34 35       30 31 32 33
!>               44 45       40 41 42 43 44
!>                  55       50 51 52 53 54 55
!>
!>
!>  Let TRANSR = 'N'. RFP holds AP as follows:
!>  For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
!>  three columns of AP upper. The lower triangle A(4:6,0:2) consists of
!>  conjugate-transpose of the first three columns of AP upper.
!>  For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
!>  three columns of AP lower. The upper triangle A(0:2,0:2) consists of
!>  conjugate-transpose of the last three columns of AP lower.
!>  To denote conjugate we place -- above the element. This covers the
!>  case N even and TRANSR = 'N'.
!>
!>         RFP A                   RFP A
!>
!>                                -- -- --
!>        03 04 05                33 43 53
!>                                   -- --
!>        13 14 15                00 44 54
!>                                      --
!>        23 24 25                10 11 55
!>
!>        33 34 35                20 21 22
!>        --
!>        00 44 45                30 31 32
!>        -- --
!>        01 11 55                40 41 42
!>        -- -- --
!>        02 12 22                50 51 52
!>
!>  Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
!>  transpose of RFP A above. One therefore gets:
!>
!>
!>           RFP A                   RFP A
!>
!>     -- -- -- --                -- -- -- -- -- --
!>     03 13 23 33 00 01 02    33 00 10 20 30 40 50
!>     -- -- -- -- --                -- -- -- -- --
!>     04 14 24 34 44 11 12    43 44 11 21 31 41 51
!>     -- -- -- -- -- --                -- -- -- --
!>     05 15 25 35 45 55 22    53 54 55 22 32 42 52
!>
!>
!>  We next  consider Standard Packed Format when N is odd.
!>  We give an example where N = 5.
!>
!>     AP is Upper                 AP is Lower
!>
!>   00 01 02 03 04              00
!>      11 12 13 14              10 11
!>         22 23 24              20 21 22
!>            33 34              30 31 32 33
!>               44              40 41 42 43 44
!>
!>
!>  Let TRANSR = 'N'. RFP holds AP as follows:
!>  For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
!>  three columns of AP upper. The lower triangle A(3:4,0:1) consists of
!>  conjugate-transpose of the first two   columns of AP upper.
!>  For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
!>  three columns of AP lower. The upper triangle A(0:1,1:2) consists of
!>  conjugate-transpose of the last two   columns of AP lower.
!>  To denote conjugate we place -- above the element. This covers the
!>  case N odd  and TRANSR = 'N'.
!>
!>         RFP A                   RFP A
!>
!>                                   -- --
!>        02 03 04                00 33 43
!>                                      --
!>        12 13 14                10 11 44
!>
!>        22 23 24                20 21 22
!>        --
!>        00 33 34                30 31 32
!>        -- --
!>        01 11 44                40 41 42
!>
!>  Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
!>  transpose of RFP A above. One therefore gets:
!>
!>
!>           RFP A                   RFP A
!>
!>     -- -- --                   -- -- -- -- -- --
!>     02 12 22 00 01             00 10 20 30 40 50
!>     -- -- -- --                   -- -- -- -- --
!>     03 13 23 33 11             33 11 21 31 41 51
!>     -- -- -- -- --                   -- -- -- --
!>     04 14 24 34 44             43 44 22 32 42 52
!> 

Definition at line 213 of file ztrttf.f.

214*
215* -- LAPACK computational routine --
216* -- LAPACK is a software package provided by Univ. of Tennessee, --
217* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
218*
219* .. Scalar Arguments ..
220 CHARACTER TRANSR, UPLO
221 INTEGER INFO, N, LDA
222* ..
223* .. Array Arguments ..
224 COMPLEX*16 A( 0: LDA-1, 0: * ), ARF( 0: * )
225* ..
226*
227* =====================================================================
228*
229* .. Parameters ..
230* ..
231* .. Local Scalars ..
232 LOGICAL LOWER, NISODD, NORMALTRANSR
233 INTEGER I, IJ, J, K, L, N1, N2, NT, NX2, NP1X2
234* ..
235* .. External Functions ..
236 LOGICAL LSAME
237 EXTERNAL lsame
238* ..
239* .. External Subroutines ..
240 EXTERNAL xerbla
241* ..
242* .. Intrinsic Functions ..
243 INTRINSIC dconjg, max, mod
244* ..
245* .. Executable Statements ..
246*
247* Test the input parameters.
248*
249 info = 0
250 normaltransr = lsame( transr, 'N' )
251 lower = lsame( uplo, 'L' )
252 IF( .NOT.normaltransr .AND. .NOT.lsame( transr, 'C' ) ) THEN
253 info = -1
254 ELSE IF( .NOT.lower .AND. .NOT.lsame( uplo, 'U' ) ) THEN
255 info = -2
256 ELSE IF( n.LT.0 ) THEN
257 info = -3
258 ELSE IF( lda.LT.max( 1, n ) ) THEN
259 info = -5
260 END IF
261 IF( info.NE.0 ) THEN
262 CALL xerbla( 'ZTRTTF', -info )
263 RETURN
264 END IF
265*
266* Quick return if possible
267*
268 IF( n.LE.1 ) THEN
269 IF( n.EQ.1 ) THEN
270 IF( normaltransr ) THEN
271 arf( 0 ) = a( 0, 0 )
272 ELSE
273 arf( 0 ) = dconjg( a( 0, 0 ) )
274 END IF
275 END IF
276 RETURN
277 END IF
278*
279* Size of array ARF(1:2,0:nt-1)
280*
281 nt = n*( n+1 ) / 2
282*
283* set N1 and N2 depending on LOWER: for N even N1=N2=K
284*
285 IF( lower ) THEN
286 n2 = n / 2
287 n1 = n - n2
288 ELSE
289 n1 = n / 2
290 n2 = n - n1
291 END IF
292*
293* If N is odd, set NISODD = .TRUE., LDA=N+1 and A is (N+1)--by--K2.
294* If N is even, set K = N/2 and NISODD = .FALSE., LDA=N and A is
295* N--by--(N+1)/2.
296*
297 IF( mod( n, 2 ).EQ.0 ) THEN
298 k = n / 2
299 nisodd = .false.
300 IF( .NOT.lower )
301 $ np1x2 = n + n + 2
302 ELSE
303 nisodd = .true.
304 IF( .NOT.lower )
305 $ nx2 = n + n
306 END IF
307*
308 IF( nisodd ) THEN
309*
310* N is odd
311*
312 IF( normaltransr ) THEN
313*
314* N is odd and TRANSR = 'N'
315*
316 IF( lower ) THEN
317*
318* SRPA for LOWER, NORMAL and N is odd ( a(0:n-1,0:n1-1) )
319* T1 -> a(0,0), T2 -> a(0,1), S -> a(n1,0)
320* T1 -> a(0), T2 -> a(n), S -> a(n1); lda=n
321*
322 ij = 0
323 DO j = 0, n2
324 DO i = n1, n2 + j
325 arf( ij ) = dconjg( a( n2+j, i ) )
326 ij = ij + 1
327 END DO
328 DO i = j, n - 1
329 arf( ij ) = a( i, j )
330 ij = ij + 1
331 END DO
332 END DO
333*
334 ELSE
335*
336* SRPA for UPPER, NORMAL and N is odd ( a(0:n-1,0:n2-1)
337* T1 -> a(n1+1,0), T2 -> a(n1,0), S -> a(0,0)
338* T1 -> a(n2), T2 -> a(n1), S -> a(0); lda=n
339*
340 ij = nt - n
341 DO j = n - 1, n1, -1
342 DO i = 0, j
343 arf( ij ) = a( i, j )
344 ij = ij + 1
345 END DO
346 DO l = j - n1, n1 - 1
347 arf( ij ) = dconjg( a( j-n1, l ) )
348 ij = ij + 1
349 END DO
350 ij = ij - nx2
351 END DO
352*
353 END IF
354*
355 ELSE
356*
357* N is odd and TRANSR = 'C'
358*
359 IF( lower ) THEN
360*
361* SRPA for LOWER, TRANSPOSE and N is odd
362* T1 -> A(0,0) , T2 -> A(1,0) , S -> A(0,n1)
363* T1 -> A(0+0) , T2 -> A(1+0) , S -> A(0+n1*n1); lda=n1
364*
365 ij = 0
366 DO j = 0, n2 - 1
367 DO i = 0, j
368 arf( ij ) = dconjg( a( j, i ) )
369 ij = ij + 1
370 END DO
371 DO i = n1 + j, n - 1
372 arf( ij ) = a( i, n1+j )
373 ij = ij + 1
374 END DO
375 END DO
376 DO j = n2, n - 1
377 DO i = 0, n1 - 1
378 arf( ij ) = dconjg( a( j, i ) )
379 ij = ij + 1
380 END DO
381 END DO
382*
383 ELSE
384*
385* SRPA for UPPER, TRANSPOSE and N is odd
386* T1 -> A(0,n1+1), T2 -> A(0,n1), S -> A(0,0)
387* T1 -> A(n2*n2), T2 -> A(n1*n2), S -> A(0); lda=n2
388*
389 ij = 0
390 DO j = 0, n1
391 DO i = n1, n - 1
392 arf( ij ) = dconjg( a( j, i ) )
393 ij = ij + 1
394 END DO
395 END DO
396 DO j = 0, n1 - 1
397 DO i = 0, j
398 arf( ij ) = a( i, j )
399 ij = ij + 1
400 END DO
401 DO l = n2 + j, n - 1
402 arf( ij ) = dconjg( a( n2+j, l ) )
403 ij = ij + 1
404 END DO
405 END DO
406*
407 END IF
408*
409 END IF
410*
411 ELSE
412*
413* N is even
414*
415 IF( normaltransr ) THEN
416*
417* N is even and TRANSR = 'N'
418*
419 IF( lower ) THEN
420*
421* SRPA for LOWER, NORMAL, and N is even ( a(0:n,0:k-1) )
422* T1 -> a(1,0), T2 -> a(0,0), S -> a(k+1,0)
423* T1 -> a(1), T2 -> a(0), S -> a(k+1); lda=n+1
424*
425 ij = 0
426 DO j = 0, k - 1
427 DO i = k, k + j
428 arf( ij ) = dconjg( a( k+j, i ) )
429 ij = ij + 1
430 END DO
431 DO i = j, n - 1
432 arf( ij ) = a( i, j )
433 ij = ij + 1
434 END DO
435 END DO
436*
437 ELSE
438*
439* SRPA for UPPER, NORMAL, and N is even ( a(0:n,0:k-1) )
440* T1 -> a(k+1,0) , T2 -> a(k,0), S -> a(0,0)
441* T1 -> a(k+1), T2 -> a(k), S -> a(0); lda=n+1
442*
443 ij = nt - n - 1
444 DO j = n - 1, k, -1
445 DO i = 0, j
446 arf( ij ) = a( i, j )
447 ij = ij + 1
448 END DO
449 DO l = j - k, k - 1
450 arf( ij ) = dconjg( a( j-k, l ) )
451 ij = ij + 1
452 END DO
453 ij = ij - np1x2
454 END DO
455*
456 END IF
457*
458 ELSE
459*
460* N is even and TRANSR = 'C'
461*
462 IF( lower ) THEN
463*
464* SRPA for LOWER, TRANSPOSE and N is even (see paper, A=B)
465* T1 -> A(0,1) , T2 -> A(0,0) , S -> A(0,k+1) :
466* T1 -> A(0+k) , T2 -> A(0+0) , S -> A(0+k*(k+1)); lda=k
467*
468 ij = 0
469 j = k
470 DO i = k, n - 1
471 arf( ij ) = a( i, j )
472 ij = ij + 1
473 END DO
474 DO j = 0, k - 2
475 DO i = 0, j
476 arf( ij ) = dconjg( a( j, i ) )
477 ij = ij + 1
478 END DO
479 DO i = k + 1 + j, n - 1
480 arf( ij ) = a( i, k+1+j )
481 ij = ij + 1
482 END DO
483 END DO
484 DO j = k - 1, n - 1
485 DO i = 0, k - 1
486 arf( ij ) = dconjg( a( j, i ) )
487 ij = ij + 1
488 END DO
489 END DO
490*
491 ELSE
492*
493* SRPA for UPPER, TRANSPOSE and N is even (see paper, A=B)
494* T1 -> A(0,k+1) , T2 -> A(0,k) , S -> A(0,0)
495* T1 -> A(0+k*(k+1)) , T2 -> A(0+k*k) , S -> A(0+0)); lda=k
496*
497 ij = 0
498 DO j = 0, k
499 DO i = k, n - 1
500 arf( ij ) = dconjg( a( j, i ) )
501 ij = ij + 1
502 END DO
503 END DO
504 DO j = 0, k - 2
505 DO i = 0, j
506 arf( ij ) = a( i, j )
507 ij = ij + 1
508 END DO
509 DO l = k + 1 + j, n - 1
510 arf( ij ) = dconjg( a( k+1+j, l ) )
511 ij = ij + 1
512 END DO
513 END DO
514*
515* Note that here J = K-1
516*
517 DO i = 0, j
518 arf( ij ) = a( i, j )
519 ij = ij + 1
520 END DO
521*
522 END IF
523*
524 END IF
525*
526 END IF
527*
528 RETURN
529*
530* End of ZTRTTF
531*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: