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

« back to all changes in this revision

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