File: ctzpad.f

package info (click to toggle)
scalapack 2.2.2-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 37,012 kB
  • sloc: fortran: 339,113; ansic: 74,517; makefile: 1,494; sh: 34
file content (247 lines) | stat: -rw-r--r-- 9,260 bytes parent folder | download | duplicates (12)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
      SUBROUTINE CTZPAD( UPLO, HERM, M, N, IOFFD, ALPHA, BETA, A, LDA )
*
*  -- PBLAS auxiliary routine (version 2.0) --
*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
*     and University of California, Berkeley.
*     April 1, 1998
*
*     .. Scalar Arguments ..
      CHARACTER*1        HERM, UPLO
      INTEGER            IOFFD, LDA, M, N
      COMPLEX            ALPHA, BETA
*     ..
*     .. Array Arguments ..
      COMPLEX            A( LDA, * )
*     ..
*
*  Purpose
*  =======
*
*  CTZPAD  initializes a two-dimensional array A to beta on the diagonal
*  specified by IOFFD or zeros the imaginary part of those diagonals and
*  set the offdiagonals to alpha.
*
*  Arguments
*  =========
*
*  UPLO    (input) CHARACTER*1
*          On entry,  UPLO  specifies  which trapezoidal part of the ar-
*          ray A is to be set as follows:
*             = 'L' or 'l':   Lower triangular part is set; the strictly
*                             upper triangular part of A is not changed,
*             = 'D' or 'd':   diagonal  specified  by  IOFFD is set; the
*                             rest of the array A is unchanged,
*             = 'U' or 'u':   Upper triangular part is set; the strictly
*                             lower triangular part of A is not changed,
*             Otherwise:      All of the array A is set.
*
*  HERM    (input) CHARACTER*1
*          On entry, HERM specifies what should be done to the diagonals
*          as follows.  When UPLO is 'L', 'l', 'D', 'd', 'U' or 'u'  and
*          HERM is  'Z'  or  'z', the imaginary part of the diagonals is
*          set  to  zero. Otherwise, the diagonals are set to beta.
*
*  M       (input) INTEGER
*          On entry,  M  specifies the number of rows of the array A.  M
*          must be at least zero.
*
*  N       (input) INTEGER
*          On entry,  N  specifies the number of columns of the array A.
*          N must be at least zero.
*
*  IOFFD   (input) INTEGER
*          On entry, IOFFD specifies the position of the offdiagonal de-
*          limiting the upper and lower trapezoidal part of A as follows
*          (see the notes below):
*
*             IOFFD = 0  specifies the main diagonal A( i, i ),
*                        with i = 1 ... MIN( M, N ),
*             IOFFD > 0  specifies the subdiagonal   A( i+IOFFD, i ),
*                        with i = 1 ... MIN( M-IOFFD, N ),
*             IOFFD < 0  specifies the superdiagonal A( i, i-IOFFD ),
*                        with i = 1 ... MIN( M, N+IOFFD ).
*
*  ALPHA   (input) COMPLEX
*          On entry,  ALPHA  specifies the scalar alpha, i.e., the value
*          to which the offdiagonal entries of the array A determined by
*          UPLO and IOFFD are set.
*
*  BETA    (input) COMPLEX
*          On entry, BETA  specifies the scalar beta, i.e., the value to
*          which the diagonal entries specified by IOFFD of the array  A
*          are set. BETA is not referenced when UPLO is 'L', 'l', 'U' or
*          'u' and HERM is 'Z'.
*
*  A       (input/output) COMPLEX array
*          On entry, A is an array of dimension  (LDA,N).  Before  entry
*          with UPLO = 'U', the leading m by n part of the array  A must
*          contain the upper trapezoidal part of the matrix to be set as
*          specified by  IOFFD,  and the strictly lower trapezoidal part
*          of A is not referenced;  When  UPLO = 'L', the leading m by n
*          part of the array A must contain the lower  trapezoidal  part
*          of  the  matrix  to  be  set  as  specified by IOFFD, and the
*          strictly upper  trapezoidal  part of A is not referenced.  On
*          exit, the entries  of the  trapezoid  part of A determined by
*          UPLO, HERM and IOFFD are set.
*
*  LDA     (input) INTEGER
*          On entry, LDA specifies the leading dimension of the array A.
*          LDA must be at least max( 1, M ).
*
*  Notes
*  =====
*                           N                                    N
*             ----------------------------                  -----------
*            |       d                    |                |           |
*          M |         d        'U'       |                |      'U'  |
*            |  'L'     'D'               |                |d          |
*            |             d              |              M |  d        |
*             ----------------------------                 |   'D'     |
*                                                          |      d    |
*               IOFFD < 0                                  | 'L'    d  |
*                                                          |          d|
*                  N                                       |           |
*             -----------                                   -----------
*            |    d   'U'|
*            |      d    |                                   IOFFD > 0
*          M |       'D' |
*            |          d|                              N
*            |  'L'      |                 ----------------------------
*            |           |                |          'U'               |
*            |           |                |d                           |
*            |           |                | 'D'                        |
*            |           |                |    d                       |
*            |           |                |'L'   d                     |
*             -----------                  ----------------------------
*
*  -- Written on April 1, 1998 by
*     Antoine Petitet, University  of  Tennessee, Knoxville 37996, USA.
*
*  =====================================================================
*
*     .. Parameters ..
      REAL               RZERO
      PARAMETER          ( RZERO = 0.0E+0 )
*     ..
*     .. Local Scalars ..
      INTEGER            I, J, JTMP, MN
*     ..
*     .. External Functions ..
      LOGICAL            LSAME
      EXTERNAL           LSAME
*     ..
*     .. Intrinsic Functions ..
      INTRINSIC          CMPLX, MAX, MIN, REAL
*     ..
*     .. Executable Statements ..
*
*     Quick return if possible
*
      IF( M.LE.0 .OR. N.LE.0 )
     $   RETURN
*
*     Start the operations
*
      IF( LSAME( UPLO, 'L' ) ) THEN
*
*        Set the diagonal to BETA or zero the imaginary part of the
*        diagonals and set the strictly lower triangular part of the
*        array to ALPHA.
*
         MN = MAX( 0, -IOFFD )
         DO 20 J = 1, MIN( MN, N )
            DO 10 I = 1, M
               A( I, J ) = ALPHA
   10       CONTINUE
   20    CONTINUE
*
         IF( LSAME( HERM, 'Z' ) ) THEN
            DO 40 J = MN + 1, MIN( M - IOFFD, N )
               JTMP = J + IOFFD
               A( JTMP, J ) = CMPLX( REAL( A( JTMP, J ) ), RZERO )
               DO 30 I = JTMP + 1, M
                  A( I, J ) = ALPHA
   30          CONTINUE
   40       CONTINUE
         ELSE
            DO 60 J = MN + 1, MIN( M - IOFFD, N )
               JTMP = J + IOFFD
               A( JTMP, J ) = BETA
               DO 50 I = JTMP + 1, M
                  A( I, J ) = ALPHA
   50          CONTINUE
   60       CONTINUE
         END IF
*
      ELSE IF( LSAME( UPLO, 'U' ) ) THEN
*
*        Set the diagonal to BETA or zero the imaginary part of the
*        diagonals and set the strictly upper triangular part of the
*        array to ALPHA.
*
         MN = MIN( M - IOFFD, N )
         IF( LSAME( HERM, 'Z' ) ) THEN
            DO 80 J = MAX( 0, -IOFFD ) + 1, MN
               JTMP = J + IOFFD
               DO 70 I = 1, JTMP - 1
                  A( I, J ) = ALPHA
   70          CONTINUE
               A( JTMP, J ) = CMPLX( REAL( A( JTMP, J ) ), RZERO )
   80       CONTINUE
         ELSE
            DO 100 J = MAX( 0, -IOFFD ) + 1, MN
               JTMP = J + IOFFD
               DO 90 I = 1, JTMP - 1
                  A( I, J ) = ALPHA
   90          CONTINUE
               A( JTMP, J ) = BETA
  100       CONTINUE
         END IF
         DO 120 J = MAX( 0, MN ) + 1, N
            DO 110 I = 1, M
               A( I, J ) = ALPHA
  110       CONTINUE
  120    CONTINUE
*
      ELSE IF( LSAME( UPLO, 'D' ) ) THEN
*
*        Set the diagonal to BETA or zero the imaginary part of the
*        diagonals.
*
         IF( LSAME( HERM, 'Z' ) ) THEN
            IF( ( IOFFD.LT.M ).AND.( IOFFD.GT.-N ) ) THEN
               DO 130 J = MAX( 0, -IOFFD ) + 1, MIN( M - IOFFD, N )
                  JTMP = J + IOFFD
                  A( JTMP, J ) = CMPLX( REAL( A( JTMP, J ) ), RZERO )
  130          CONTINUE
            END IF
         ELSE
            IF( ( IOFFD.LT.M ).AND.( IOFFD.GT.-N ) ) THEN
               DO 140 J = MAX( 0, -IOFFD ) + 1, MIN( M - IOFFD, N )
                  A( J + IOFFD, J ) = BETA
  140          CONTINUE
            END IF
         END IF
*
      ELSE
*
*        Set the diagonals to BETA and the offdiagonals to ALPHA.
*
         DO 160 J = 1, N
            DO 150 I = 1, M
               A( I, J ) = ALPHA
  150       CONTINUE
  160    CONTINUE
         IF( ALPHA.NE.BETA .AND. IOFFD.LT.M .AND. IOFFD.GT.-N ) THEN
            DO 170 J = MAX( 0, -IOFFD ) + 1, MIN( M - IOFFD, N )
               A( J + IOFFD, J ) = BETA
  170       CONTINUE
         END IF
*
      END IF
*
      RETURN
*
*     End of CTZPAD
*
      END