~ubuntu-branches/ubuntu/trusty/nwchem/trusty-proposed

« back to all changes in this revision

Viewing changes to src/blas/single/cgemv.f

  • Committer: Package Import Robot
  • Author(s): Michael Banck, Daniel Leidert, Andreas Tille, Michael Banck
  • Date: 2013-07-04 12:14:55 UTC
  • mfrom: (1.1.2)
  • Revision ID: package-import@ubuntu.com-20130704121455-5tvsx2qabor3nrui
Tags: 6.3-1
* New upstream release.
* Fixes anisotropic properties (Closes: #696361).
* New features include:
  + Multi-reference coupled cluster (MRCC) approaches
  + Hybrid DFT calculations with short-range HF 
  + New density-functionals including Minnesota (M08, M11) and HSE hybrid
    functionals
  + X-ray absorption spectroscopy (XAS) with TDDFT
  + Analytical gradients for the COSMO solvation model
  + Transition densities from TDDFT 
  + DFT+U and Electron-Transfer (ET) methods for plane wave calculations
  + Exploitation of space group symmetry in plane wave geometry optimizations
  + Local density of states (LDOS) collective variable added to Metadynamics
  + Various new XC functionals added for plane wave calculations, including
    hybrid and range-corrected ones
  + Electric field gradients with relativistic corrections 
  + Nudged Elastic Band optimization method
  + Updated basis sets and ECPs 

[ Daniel Leidert ]
* debian/watch: Fixed.

[ Andreas Tille ]
* debian/upstream: References

[ Michael Banck ]
* debian/upstream (Name): New field.
* debian/patches/02_makefile_flags.patch: Refreshed.
* debian/patches/06_statfs_kfreebsd.patch: Likewise.
* debian/patches/07_ga_target_force_linux.patch: Likewise.
* debian/patches/05_avoid_inline_assembler.patch: Removed, no longer needed.
* debian/patches/09_backported_6.1.1_fixes.patch: Likewise.
* debian/control (Build-Depends): Added gfortran-4.7 and gcc-4.7.
* debian/patches/10_force_gcc-4.7.patch: New patch, explicitly sets
  gfortran-4.7 and gcc-4.7, fixes test suite hang with gcc-4.8 (Closes:
  #701328, #713262).
* debian/testsuite: Added tests for COSMO analytical gradients and MRCC.
* debian/rules (MRCC_METHODS): New variable, required to enable MRCC methods.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
      SUBROUTINE CGEMV ( TRANS, M, N, ALPHA, A, LDA, X, INCX,
2
 
     $                   BETA, Y, INCY )
3
 
*
4
 
* $Id: cgemv.f 19695 2010-10-29 16:51:02Z d3y133 $
 
1
*> \brief \b CGEMV
 
2
*
 
3
*  =========== DOCUMENTATION ===========
 
4
*
 
5
* Online html documentation available at 
 
6
*            http://www.netlib.org/lapack/explore-html/ 
 
7
*
 
8
*  Definition:
 
9
*  ===========
 
10
*
 
11
*       SUBROUTINE CGEMV(TRANS,M,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
 
12
 
13
*       .. Scalar Arguments ..
 
14
*       COMPLEX ALPHA,BETA
 
15
*       INTEGER INCX,INCY,LDA,M,N
 
16
*       CHARACTER TRANS
 
17
*       ..
 
18
*       .. Array Arguments ..
 
19
*       COMPLEX A(LDA,*),X(*),Y(*)
 
20
*       ..
 
21
*  
 
22
*
 
23
*> \par Purpose:
 
24
*  =============
 
25
*>
 
26
*> \verbatim
 
27
*>
 
28
*> CGEMV performs one of the matrix-vector operations
 
29
*>
 
30
*>    y := alpha*A*x + beta*y,   or   y := alpha*A**T*x + beta*y,   or
 
31
*>
 
32
*>    y := alpha*A**H*x + beta*y,
 
33
*>
 
34
*> where alpha and beta are scalars, x and y are vectors and A is an
 
35
*> m by n matrix.
 
36
*> \endverbatim
 
37
*
 
38
*  Arguments:
 
39
*  ==========
 
40
*
 
41
*> \param[in] TRANS
 
42
*> \verbatim
 
43
*>          TRANS is CHARACTER*1
 
44
*>           On entry, TRANS specifies the operation to be performed as
 
45
*>           follows:
 
46
*>
 
47
*>              TRANS = 'N' or 'n'   y := alpha*A*x + beta*y.
 
48
*>
 
49
*>              TRANS = 'T' or 't'   y := alpha*A**T*x + beta*y.
 
50
*>
 
51
*>              TRANS = 'C' or 'c'   y := alpha*A**H*x + beta*y.
 
52
*> \endverbatim
 
53
*>
 
54
*> \param[in] M
 
55
*> \verbatim
 
56
*>          M is INTEGER
 
57
*>           On entry, M specifies the number of rows of the matrix A.
 
58
*>           M must be at least zero.
 
59
*> \endverbatim
 
60
*>
 
61
*> \param[in] N
 
62
*> \verbatim
 
63
*>          N is INTEGER
 
64
*>           On entry, N specifies the number of columns of the matrix A.
 
65
*>           N must be at least zero.
 
66
*> \endverbatim
 
67
*>
 
68
*> \param[in] ALPHA
 
69
*> \verbatim
 
70
*>          ALPHA is COMPLEX
 
71
*>           On entry, ALPHA specifies the scalar alpha.
 
72
*> \endverbatim
 
73
*>
 
74
*> \param[in] A
 
75
*> \verbatim
 
76
*>          A is COMPLEX array of DIMENSION ( LDA, n ).
 
77
*>           Before entry, the leading m by n part of the array A must
 
78
*>           contain the matrix of coefficients.
 
79
*> \endverbatim
 
80
*>
 
81
*> \param[in] LDA
 
82
*> \verbatim
 
83
*>          LDA is INTEGER
 
84
*>           On entry, LDA specifies the first dimension of A as declared
 
85
*>           in the calling (sub) program. LDA must be at least
 
86
*>           max( 1, m ).
 
87
*> \endverbatim
 
88
*>
 
89
*> \param[in] X
 
90
*> \verbatim
 
91
*>          X is COMPLEX array of DIMENSION at least
 
92
*>           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
 
93
*>           and at least
 
94
*>           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
 
95
*>           Before entry, the incremented array X must contain the
 
96
*>           vector x.
 
97
*> \endverbatim
 
98
*>
 
99
*> \param[in] INCX
 
100
*> \verbatim
 
101
*>          INCX is INTEGER
 
102
*>           On entry, INCX specifies the increment for the elements of
 
103
*>           X. INCX must not be zero.
 
104
*> \endverbatim
 
105
*>
 
106
*> \param[in] BETA
 
107
*> \verbatim
 
108
*>          BETA is COMPLEX
 
109
*>           On entry, BETA specifies the scalar beta. When BETA is
 
110
*>           supplied as zero then Y need not be set on input.
 
111
*> \endverbatim
 
112
*>
 
113
*> \param[in,out] Y
 
114
*> \verbatim
 
115
*>          Y is COMPLEX array of DIMENSION at least
 
116
*>           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
 
117
*>           and at least
 
118
*>           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
 
119
*>           Before entry with BETA non-zero, the incremented array Y
 
120
*>           must contain the vector y. On exit, Y is overwritten by the
 
121
*>           updated vector y.
 
122
*> \endverbatim
 
123
*>
 
124
*> \param[in] INCY
 
125
*> \verbatim
 
126
*>          INCY is INTEGER
 
127
*>           On entry, INCY specifies the increment for the elements of
 
128
*>           Y. INCY must not be zero.
 
129
*> \endverbatim
 
130
*
 
131
*  Authors:
 
132
*  ========
 
133
*
 
134
*> \author Univ. of Tennessee 
 
135
*> \author Univ. of California Berkeley 
 
136
*> \author Univ. of Colorado Denver 
 
137
*> \author NAG Ltd. 
 
138
*
 
139
*> \date November 2011
 
140
*
 
141
*> \ingroup complex_blas_level2
 
142
*
 
143
*> \par Further Details:
 
144
*  =====================
 
145
*>
 
146
*> \verbatim
 
147
*>
 
148
*>  Level 2 Blas routine.
 
149
*>  The vector and matrix arguments are not referenced when N = 0, or M = 0
 
150
*>
 
151
*>  -- Written on 22-October-1986.
 
152
*>     Jack Dongarra, Argonne National Lab.
 
153
*>     Jeremy Du Croz, Nag Central Office.
 
154
*>     Sven Hammarling, Nag Central Office.
 
155
*>     Richard Hanson, Sandia National Labs.
 
156
*> \endverbatim
 
157
*>
 
158
*  =====================================================================
 
159
      SUBROUTINE CGEMV(TRANS,M,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
 
160
*
 
161
*  -- Reference BLAS level2 routine (version 3.4.0) --
 
162
*  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --
 
163
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 
164
*     November 2011
5
165
*
6
166
*     .. Scalar Arguments ..
7
 
      COMPLEX            ALPHA, BETA
8
 
      INTEGER            INCX, INCY, LDA, M, N
9
 
      CHARACTER*1        TRANS
 
167
      COMPLEX ALPHA,BETA
 
168
      INTEGER INCX,INCY,LDA,M,N
 
169
      CHARACTER TRANS
 
170
*     ..
10
171
*     .. Array Arguments ..
11
 
      COMPLEX            A( LDA, * ), X( * ), Y( * )
 
172
      COMPLEX A(LDA,*),X(*),Y(*)
12
173
*     ..
13
174
*
14
 
*  Purpose
15
 
*  =======
16
 
*
17
 
*  CGEMV  performs one of the matrix-vector operations
18
 
*
19
 
*     y := alpha*A*x + beta*y,   or   y := alpha*A'*x + beta*y,   or
20
 
*
21
 
*     y := alpha*conjg( A' )*x + beta*y,
22
 
*
23
 
*  where alpha and beta are scalars, x and y are vectors and A is an
24
 
*  m by n matrix.
25
 
*
26
 
*  Parameters
27
 
*  ==========
28
 
*
29
 
*  TRANS  - CHARACTER*1.
30
 
*           On entry, TRANS specifies the operation to be performed as
31
 
*           follows:
32
 
*
33
 
*              TRANS = 'N' or 'n'   y := alpha*A*x + beta*y.
34
 
*
35
 
*              TRANS = 'T' or 't'   y := alpha*A'*x + beta*y.
36
 
*
37
 
*              TRANS = 'C' or 'c'   y := alpha*conjg( A' )*x + beta*y.
38
 
*
39
 
*           Unchanged on exit.
40
 
*
41
 
*  M      - INTEGER.
42
 
*           On entry, M specifies the number of rows of the matrix A.
43
 
*           M must be at least zero.
44
 
*           Unchanged on exit.
45
 
*
46
 
*  N      - INTEGER.
47
 
*           On entry, N specifies the number of columns of the matrix A.
48
 
*           N must be at least zero.
49
 
*           Unchanged on exit.
50
 
*
51
 
*  ALPHA  - COMPLEX         .
52
 
*           On entry, ALPHA specifies the scalar alpha.
53
 
*           Unchanged on exit.
54
 
*
55
 
*  A      - COMPLEX          array of DIMENSION ( LDA, n ).
56
 
*           Before entry, the leading m by n part of the array A must
57
 
*           contain the matrix of coefficients.
58
 
*           Unchanged on exit.
59
 
*
60
 
*  LDA    - INTEGER.
61
 
*           On entry, LDA specifies the first dimension of A as declared
62
 
*           in the calling (sub) program. LDA must be at least
63
 
*           max( 1, m ).
64
 
*           Unchanged on exit.
65
 
*
66
 
*  X      - COMPLEX          array of DIMENSION at least
67
 
*           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
68
 
*           and at least
69
 
*           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
70
 
*           Before entry, the incremented array X must contain the
71
 
*           vector x.
72
 
*           Unchanged on exit.
73
 
*
74
 
*  INCX   - INTEGER.
75
 
*           On entry, INCX specifies the increment for the elements of
76
 
*           X. INCX must not be zero.
77
 
*           Unchanged on exit.
78
 
*
79
 
*  BETA   - COMPLEX         .
80
 
*           On entry, BETA specifies the scalar beta. When BETA is
81
 
*           supplied as zero then Y need not be set on input.
82
 
*           Unchanged on exit.
83
 
*
84
 
*  Y      - COMPLEX          array of DIMENSION at least
85
 
*           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
86
 
*           and at least
87
 
*           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
88
 
*           Before entry with BETA non-zero, the incremented array Y
89
 
*           must contain the vector y. On exit, Y is overwritten by the
90
 
*           updated vector y.
91
 
*
92
 
*  INCY   - INTEGER.
93
 
*           On entry, INCY specifies the increment for the elements of
94
 
*           Y. INCY must not be zero.
95
 
*           Unchanged on exit.
96
 
*
97
 
*
98
 
*  Level 2 Blas routine.
99
 
*
100
 
*  -- Written on 22-October-1986.
101
 
*     Jack Dongarra, Argonne National Lab.
102
 
*     Jeremy Du Croz, Nag Central Office.
103
 
*     Sven Hammarling, Nag Central Office.
104
 
*     Richard Hanson, Sandia National Labs.
105
 
*
 
175
*  =====================================================================
106
176
*
107
177
*     .. Parameters ..
108
 
      COMPLEX            ONE
109
 
      PARAMETER        ( ONE  = ( 1.0E+0, 0.0E+0 ) )
110
 
      COMPLEX            ZERO
111
 
      PARAMETER        ( ZERO = ( 0.0E+0, 0.0E+0 ) )
 
178
      COMPLEX ONE
 
179
      PARAMETER (ONE= (1.0E+0,0.0E+0))
 
180
      COMPLEX ZERO
 
181
      PARAMETER (ZERO= (0.0E+0,0.0E+0))
 
182
*     ..
112
183
*     .. Local Scalars ..
113
 
      COMPLEX            TEMP
114
 
      INTEGER            I, INFO, IX, IY, J, JX, JY, KX, KY, LENX, LENY
115
 
      LOGICAL            NOCONJ
 
184
      COMPLEX TEMP
 
185
      INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY,LENX,LENY
 
186
      LOGICAL NOCONJ
 
187
*     ..
116
188
*     .. External Functions ..
117
 
      LOGICAL            LSAME
118
 
      EXTERNAL           LSAME
 
189
      LOGICAL LSAME
 
190
      EXTERNAL LSAME
 
191
*     ..
119
192
*     .. External Subroutines ..
120
 
      EXTERNAL           XERBLA
 
193
      EXTERNAL XERBLA
 
194
*     ..
121
195
*     .. Intrinsic Functions ..
122
 
      INTRINSIC          CONJG, MAX
 
196
      INTRINSIC CONJG,MAX
123
197
*     ..
124
 
*     .. Executable Statements ..
125
198
*
126
199
*     Test the input parameters.
127
200
*
128
201
      INFO = 0
129
 
      IF     ( .NOT.LSAME( TRANS, 'N' ).AND.
130
 
     $         .NOT.LSAME( TRANS, 'T' ).AND.
131
 
     $         .NOT.LSAME( TRANS, 'C' )      )THEN
132
 
         INFO = 1
133
 
      ELSE IF( M.LT.0 )THEN
134
 
         INFO = 2
135
 
      ELSE IF( N.LT.0 )THEN
136
 
         INFO = 3
137
 
      ELSE IF( LDA.LT.MAX( 1, M ) )THEN
138
 
         INFO = 6
139
 
      ELSE IF( INCX.EQ.0 )THEN
140
 
         INFO = 8
141
 
      ELSE IF( INCY.EQ.0 )THEN
142
 
         INFO = 11
 
202
      IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
 
203
     +    .NOT.LSAME(TRANS,'C')) THEN
 
204
          INFO = 1
 
205
      ELSE IF (M.LT.0) THEN
 
206
          INFO = 2
 
207
      ELSE IF (N.LT.0) THEN
 
208
          INFO = 3
 
209
      ELSE IF (LDA.LT.MAX(1,M)) THEN
 
210
          INFO = 6
 
211
      ELSE IF (INCX.EQ.0) THEN
 
212
          INFO = 8
 
213
      ELSE IF (INCY.EQ.0) THEN
 
214
          INFO = 11
143
215
      END IF
144
 
      IF( INFO.NE.0 )THEN
145
 
         CALL XERBLA( 'CGEMV ', INFO )
146
 
         RETURN
 
216
      IF (INFO.NE.0) THEN
 
217
          CALL XERBLA('CGEMV ',INFO)
 
218
          RETURN
147
219
      END IF
148
220
*
149
221
*     Quick return if possible.
150
222
*
151
 
      IF( ( M.EQ.0 ).OR.( N.EQ.0 ).OR.
152
 
     $    ( ( ALPHA.EQ.ZERO ).AND.( BETA.EQ.ONE ) ) )
153
 
     $   RETURN
 
223
      IF ((M.EQ.0) .OR. (N.EQ.0) .OR.
 
224
     +    ((ALPHA.EQ.ZERO).AND. (BETA.EQ.ONE))) RETURN
154
225
*
155
 
      NOCONJ = LSAME( TRANS, 'T' )
 
226
      NOCONJ = LSAME(TRANS,'T')
156
227
*
157
228
*     Set  LENX  and  LENY, the lengths of the vectors x and y, and set
158
229
*     up the start points in  X  and  Y.
159
230
*
160
 
      IF( LSAME( TRANS, 'N' ) )THEN
161
 
         LENX = N
162
 
         LENY = M
163
 
      ELSE
164
 
         LENX = M
165
 
         LENY = N
166
 
      END IF
167
 
      IF( INCX.GT.0 )THEN
168
 
         KX = 1
169
 
      ELSE
170
 
         KX = 1 - ( LENX - 1 )*INCX
171
 
      END IF
172
 
      IF( INCY.GT.0 )THEN
173
 
         KY = 1
174
 
      ELSE
175
 
         KY = 1 - ( LENY - 1 )*INCY
 
231
      IF (LSAME(TRANS,'N')) THEN
 
232
          LENX = N
 
233
          LENY = M
 
234
      ELSE
 
235
          LENX = M
 
236
          LENY = N
 
237
      END IF
 
238
      IF (INCX.GT.0) THEN
 
239
          KX = 1
 
240
      ELSE
 
241
          KX = 1 - (LENX-1)*INCX
 
242
      END IF
 
243
      IF (INCY.GT.0) THEN
 
244
          KY = 1
 
245
      ELSE
 
246
          KY = 1 - (LENY-1)*INCY
176
247
      END IF
177
248
*
178
249
*     Start the operations. In this version the elements of A are
180
251
*
181
252
*     First form  y := beta*y.
182
253
*
183
 
      IF( BETA.NE.ONE )THEN
184
 
         IF( INCY.EQ.1 )THEN
185
 
            IF( BETA.EQ.ZERO )THEN
186
 
               DO 10, I = 1, LENY
187
 
                  Y( I ) = ZERO
188
 
   10          CONTINUE
189
 
            ELSE
190
 
               DO 20, I = 1, LENY
191
 
                  Y( I ) = BETA*Y( I )
192
 
   20          CONTINUE
193
 
            END IF
194
 
         ELSE
195
 
            IY = KY
196
 
            IF( BETA.EQ.ZERO )THEN
197
 
               DO 30, I = 1, LENY
198
 
                  Y( IY ) = ZERO
199
 
                  IY      = IY   + INCY
200
 
   30          CONTINUE
201
 
            ELSE
202
 
               DO 40, I = 1, LENY
203
 
                  Y( IY ) = BETA*Y( IY )
204
 
                  IY      = IY           + INCY
205
 
   40          CONTINUE
206
 
            END IF
207
 
         END IF
 
254
      IF (BETA.NE.ONE) THEN
 
255
          IF (INCY.EQ.1) THEN
 
256
              IF (BETA.EQ.ZERO) THEN
 
257
                  DO 10 I = 1,LENY
 
258
                      Y(I) = ZERO
 
259
   10             CONTINUE
 
260
              ELSE
 
261
                  DO 20 I = 1,LENY
 
262
                      Y(I) = BETA*Y(I)
 
263
   20             CONTINUE
 
264
              END IF
 
265
          ELSE
 
266
              IY = KY
 
267
              IF (BETA.EQ.ZERO) THEN
 
268
                  DO 30 I = 1,LENY
 
269
                      Y(IY) = ZERO
 
270
                      IY = IY + INCY
 
271
   30             CONTINUE
 
272
              ELSE
 
273
                  DO 40 I = 1,LENY
 
274
                      Y(IY) = BETA*Y(IY)
 
275
                      IY = IY + INCY
 
276
   40             CONTINUE
 
277
              END IF
 
278
          END IF
208
279
      END IF
209
 
      IF( ALPHA.EQ.ZERO )
210
 
     $   RETURN
211
 
      IF( LSAME( TRANS, 'N' ) )THEN
 
280
      IF (ALPHA.EQ.ZERO) RETURN
 
281
      IF (LSAME(TRANS,'N')) THEN
212
282
*
213
283
*        Form  y := alpha*A*x + y.
214
284
*
215
 
         JX = KX
216
 
         IF( INCY.EQ.1 )THEN
217
 
            DO 60, J = 1, N
218
 
               IF( X( JX ).NE.ZERO )THEN
219
 
                  TEMP = ALPHA*X( JX )
220
 
                  DO 50, I = 1, M
221
 
                     Y( I ) = Y( I ) + TEMP*A( I, J )
222
 
   50             CONTINUE
223
 
               END IF
224
 
               JX = JX + INCX
225
 
   60       CONTINUE
226
 
         ELSE
227
 
            DO 80, J = 1, N
228
 
               IF( X( JX ).NE.ZERO )THEN
229
 
                  TEMP = ALPHA*X( JX )
230
 
                  IY   = KY
231
 
                  DO 70, I = 1, M
232
 
                     Y( IY ) = Y( IY ) + TEMP*A( I, J )
233
 
                     IY      = IY      + INCY
234
 
   70             CONTINUE
235
 
               END IF
236
 
               JX = JX + INCX
237
 
   80       CONTINUE
238
 
         END IF
 
285
          JX = KX
 
286
          IF (INCY.EQ.1) THEN
 
287
              DO 60 J = 1,N
 
288
                  IF (X(JX).NE.ZERO) THEN
 
289
                      TEMP = ALPHA*X(JX)
 
290
                      DO 50 I = 1,M
 
291
                          Y(I) = Y(I) + TEMP*A(I,J)
 
292
   50                 CONTINUE
 
293
                  END IF
 
294
                  JX = JX + INCX
 
295
   60         CONTINUE
 
296
          ELSE
 
297
              DO 80 J = 1,N
 
298
                  IF (X(JX).NE.ZERO) THEN
 
299
                      TEMP = ALPHA*X(JX)
 
300
                      IY = KY
 
301
                      DO 70 I = 1,M
 
302
                          Y(IY) = Y(IY) + TEMP*A(I,J)
 
303
                          IY = IY + INCY
 
304
   70                 CONTINUE
 
305
                  END IF
 
306
                  JX = JX + INCX
 
307
   80         CONTINUE
 
308
          END IF
239
309
      ELSE
240
310
*
241
 
*        Form  y := alpha*A'*x + y  or  y := alpha*conjg( A' )*x + y.
 
311
*        Form  y := alpha*A**T*x + y  or  y := alpha*A**H*x + y.
242
312
*
243
 
         JY = KY
244
 
         IF( INCX.EQ.1 )THEN
245
 
            DO 110, J = 1, N
246
 
               TEMP = ZERO
247
 
               IF( NOCONJ )THEN
248
 
                  DO 90, I = 1, M
249
 
                     TEMP = TEMP + A( I, J )*X( I )
250
 
   90             CONTINUE
251
 
               ELSE
252
 
                  DO 100, I = 1, M
253
 
                     TEMP = TEMP + CONJG( A( I, J ) )*X( I )
254
 
  100             CONTINUE
255
 
               END IF
256
 
               Y( JY ) = Y( JY ) + ALPHA*TEMP
257
 
               JY      = JY      + INCY
258
 
  110       CONTINUE
259
 
         ELSE
260
 
            DO 140, J = 1, N
261
 
               TEMP = ZERO
262
 
               IX   = KX
263
 
               IF( NOCONJ )THEN
264
 
                  DO 120, I = 1, M
265
 
                     TEMP = TEMP + A( I, J )*X( IX )
266
 
                     IX   = IX   + INCX
267
 
  120             CONTINUE
268
 
               ELSE
269
 
                  DO 130, I = 1, M
270
 
                     TEMP = TEMP + CONJG( A( I, J ) )*X( IX )
271
 
                     IX   = IX   + INCX
272
 
  130             CONTINUE
273
 
               END IF
274
 
               Y( JY ) = Y( JY ) + ALPHA*TEMP
275
 
               JY      = JY      + INCY
276
 
  140       CONTINUE
277
 
         END IF
 
313
          JY = KY
 
314
          IF (INCX.EQ.1) THEN
 
315
              DO 110 J = 1,N
 
316
                  TEMP = ZERO
 
317
                  IF (NOCONJ) THEN
 
318
                      DO 90 I = 1,M
 
319
                          TEMP = TEMP + A(I,J)*X(I)
 
320
   90                 CONTINUE
 
321
                  ELSE
 
322
                      DO 100 I = 1,M
 
323
                          TEMP = TEMP + CONJG(A(I,J))*X(I)
 
324
  100                 CONTINUE
 
325
                  END IF
 
326
                  Y(JY) = Y(JY) + ALPHA*TEMP
 
327
                  JY = JY + INCY
 
328
  110         CONTINUE
 
329
          ELSE
 
330
              DO 140 J = 1,N
 
331
                  TEMP = ZERO
 
332
                  IX = KX
 
333
                  IF (NOCONJ) THEN
 
334
                      DO 120 I = 1,M
 
335
                          TEMP = TEMP + A(I,J)*X(IX)
 
336
                          IX = IX + INCX
 
337
  120                 CONTINUE
 
338
                  ELSE
 
339
                      DO 130 I = 1,M
 
340
                          TEMP = TEMP + CONJG(A(I,J))*X(IX)
 
341
                          IX = IX + INCX
 
342
  130                 CONTINUE
 
343
                  END IF
 
344
                  Y(JY) = Y(JY) + ALPHA*TEMP
 
345
                  JY = JY + INCY
 
346
  140         CONTINUE
 
347
          END IF
278
348
      END IF
279
349
*
280
350
      RETURN