Previous Next Contents Generated Index Doc Set Home



Transpose Array

The subroutines described in this section perform an in-place or out-of-place transpose on a two-dimensional array.

Calling Sequence

CALL DTRANS
(PLACE, DSCALE, DSOURCE, M, N, DDEST)
CALL STRANS
(PLACE, SSCALE, SSOURCE, M, N, SDEST)
CALL ZTRANS
(PLACE, ZSCALE, ZSOURCE, M, N, ZDEST)
CALL CTRANS
(PLACE, CSCALE, CSOURCE, M, N, CDEST)






void dtrans
(char place, double dscale, double *dsource, int m, int 
n, double *ddest)
void strans
(char place, float sscale, float *ssource, int m, int 
n, float *sdest)
void ztrans
(char place, doublecomplex zscale, doublecomplex 
*zsource, int m, int n, doublecomplex *zdest)
void ctrans
(char place, complex cscale, complex *csource, int m, 
int n, complex *cdest)

Arguments

PLACE

Indicates whether transpose is in-place or out-of-place.

`I' or `i'

In-place; transpose from SOURCE into SOURCE.

`O' or `o'

Out-of-place; transpose from SOURCE into DEST.

xSCALE

The scale factor for the transpose.

xSOURCE

On entry, the matrix to be transposed.
On exit, if PLACE = `I' or `i', the transposed matrix; otherwise PLACE is not used.

M

Number of rows in xSOURCE.

N

Number of columns in xSOURCE.

xDEST

On exit, if PLACE = `O' or `o', the transposed matrix. If PLACE = `I' or `i', xDEST is not used.

Sample Program




      PROGRAM TEST
      IMPLICIT NONE
C
      INTEGER           M, N
      PARAMETER        (M = 4)
      PARAMETER        (N = 3)
C
      DOUBLE COMPLEX    A(M,N), ALPHA, B(N,M)
      INTEGER           I, J
C
      EXTERNAL          ZTRANS
C
      INTRINSIC         DCMPLX
C
C     Initialize the array A to store the general matrix A below:
C
C         (1.0, 1.0)  (1.0, 2.0)  (1.0, 3.0)
C     A = (2.0, 1.0)  (2.0, 2.0)  (2.0, 3.0)
C         (3.0, 1.0)  (3.0, 2.0)  (3.0, 3.0)
C         (4.0, 1.0)  (4.0, 2.0)  (4.0, 3.0)
C
      DO 110, J = 1, N
        DO 100, I = 1, M
          A(I,J) = DCMPLX (I,J)
  100   CONTINUE
  110 CONTINUE
      PRINT 1000
      DO 120, I = 1, M
        PRINT 1010, (A(I,J), J = 1, N)
  120 CONTINUE
      ALPHA = DCMPLX (1.0D0, 0.0D0)
      CALL ZTRANS (`OUT-OF-PLACE', ALPHA, A, M, N, B)
      PRINT 1020
      DO 130, I = 1, N
        PRINT 1010, (B(I,J), J = 1, M)
  130 CONTINUE
C
 1000 FORMAT (1X, `A:')
 1010 FORMAT (1X, 4(2X, `(`F4.1, `,', F4.1, `)' :))
 1020 FORMAT (/1X, `TRANS(A):')
C
      END



Sample Output




 A:
   ( 1.0, 1.0)  ( 1.0, 2.0)  ( 1.0, 3.0)
   ( 2.0, 1.0)  ( 2.0, 2.0)  ( 2.0, 3.0)
   ( 3.0, 1.0)  ( 3.0, 2.0)  ( 3.0, 3.0)
   ( 4.0, 1.0)  ( 4.0, 2.0)  ( 4.0, 3.0)



 TRANS(A):
   ( 1.0, 1.0)  ( 2.0, 1.0)  ( 3.0, 1.0)  ( 4.0, 1.0)
   ( 1.0, 2.0)  ( 2.0, 2.0)  ( 3.0, 2.0)  ( 4.0, 2.0)
   ( 1.0, 3.0)  ( 2.0, 3.0)  ( 3.0, 3.0)  ( 4.0, 3.0)






Previous Next Contents Generated Index Doc Set Home