LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dgemm.f
Go to the documentation of this file.
1*> \brief \b DGEMM
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 DGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
12*
13* .. Scalar Arguments ..
14* DOUBLE PRECISION ALPHA,BETA
15* INTEGER K,LDA,LDB,LDC,M,N
16* CHARACTER TRANSA,TRANSB
17* ..
18* .. Array Arguments ..
19* DOUBLE PRECISION A(LDA,*),B(LDB,*),C(LDC,*)
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> DGEMM performs one of the matrix-matrix operations
29*>
30*> C := alpha*op( A )*op( B ) + beta*C,
31*>
32*> where op( X ) is one of
33*>
34*> op( X ) = X or op( X ) = X**T,
35*>
36*> alpha and beta are scalars, and A, B and C are matrices, with op( A )
37*> an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] TRANSA
44*> \verbatim
45*> TRANSA is CHARACTER*1
46*> On entry, TRANSA specifies the form of op( A ) to be used in
47*> the matrix multiplication as follows:
48*>
49*> TRANSA = 'N' or 'n', op( A ) = A.
50*>
51*> TRANSA = 'T' or 't', op( A ) = A**T.
52*>
53*> TRANSA = 'C' or 'c', op( A ) = A**T.
54*> \endverbatim
55*>
56*> \param[in] TRANSB
57*> \verbatim
58*> TRANSB is CHARACTER*1
59*> On entry, TRANSB specifies the form of op( B ) to be used in
60*> the matrix multiplication as follows:
61*>
62*> TRANSB = 'N' or 'n', op( B ) = B.
63*>
64*> TRANSB = 'T' or 't', op( B ) = B**T.
65*>
66*> TRANSB = 'C' or 'c', op( B ) = B**T.
67*> \endverbatim
68*>
69*> \param[in] M
70*> \verbatim
71*> M is INTEGER
72*> On entry, M specifies the number of rows of the matrix
73*> op( A ) and of the matrix C. M must be at least zero.
74*> \endverbatim
75*>
76*> \param[in] N
77*> \verbatim
78*> N is INTEGER
79*> On entry, N specifies the number of columns of the matrix
80*> op( B ) and the number of columns of the matrix C. N must be
81*> at least zero.
82*> \endverbatim
83*>
84*> \param[in] K
85*> \verbatim
86*> K is INTEGER
87*> On entry, K specifies the number of columns of the matrix
88*> op( A ) and the number of rows of the matrix op( B ). K must
89*> be at least zero.
90*> \endverbatim
91*>
92*> \param[in] ALPHA
93*> \verbatim
94*> ALPHA is DOUBLE PRECISION.
95*> On entry, ALPHA specifies the scalar alpha.
96*> \endverbatim
97*>
98*> \param[in] A
99*> \verbatim
100*> A is DOUBLE PRECISION array, dimension ( LDA, ka ), where ka is
101*> k when TRANSA = 'N' or 'n', and is m otherwise.
102*> Before entry with TRANSA = 'N' or 'n', the leading m by k
103*> part of the array A must contain the matrix A, otherwise
104*> the leading k by m part of the array A must contain the
105*> matrix A.
106*> \endverbatim
107*>
108*> \param[in] LDA
109*> \verbatim
110*> LDA is INTEGER
111*> On entry, LDA specifies the first dimension of A as declared
112*> in the calling (sub) program. When TRANSA = 'N' or 'n' then
113*> LDA must be at least max( 1, m ), otherwise LDA must be at
114*> least max( 1, k ).
115*> \endverbatim
116*>
117*> \param[in] B
118*> \verbatim
119*> B is DOUBLE PRECISION array, dimension ( LDB, kb ), where kb is
120*> n when TRANSB = 'N' or 'n', and is k otherwise.
121*> Before entry with TRANSB = 'N' or 'n', the leading k by n
122*> part of the array B must contain the matrix B, otherwise
123*> the leading n by k part of the array B must contain the
124*> matrix B.
125*> \endverbatim
126*>
127*> \param[in] LDB
128*> \verbatim
129*> LDB is INTEGER
130*> On entry, LDB specifies the first dimension of B as declared
131*> in the calling (sub) program. When TRANSB = 'N' or 'n' then
132*> LDB must be at least max( 1, k ), otherwise LDB must be at
133*> least max( 1, n ).
134*> \endverbatim
135*>
136*> \param[in] BETA
137*> \verbatim
138*> BETA is DOUBLE PRECISION.
139*> On entry, BETA specifies the scalar beta. When BETA is
140*> supplied as zero then C need not be set on input.
141*> \endverbatim
142*>
143*> \param[in,out] C
144*> \verbatim
145*> C is DOUBLE PRECISION array, dimension ( LDC, N )
146*> Before entry, the leading m by n part of the array C must
147*> contain the matrix C, except when beta is zero, in which
148*> case C need not be set on entry.
149*> On exit, the array C is overwritten by the m by n matrix
150*> ( alpha*op( A )*op( B ) + beta*C ).
151*> \endverbatim
152*>
153*> \param[in] LDC
154*> \verbatim
155*> LDC is INTEGER
156*> On entry, LDC specifies the first dimension of C as declared
157*> in the calling (sub) program. LDC must be at least
158*> max( 1, m ).
159*> \endverbatim
160*
161* Authors:
162* ========
163*
164*> \author Univ. of Tennessee
165*> \author Univ. of California Berkeley
166*> \author Univ. of Colorado Denver
167*> \author NAG Ltd.
168*
169*> \ingroup gemm
170*
171*> \par Further Details:
172* =====================
173*>
174*> \verbatim
175*>
176*> Level 3 Blas routine.
177*>
178*> -- Written on 8-February-1989.
179*> Jack Dongarra, Argonne National Laboratory.
180*> Iain Duff, AERE Harwell.
181*> Jeremy Du Croz, Numerical Algorithms Group Ltd.
182*> Sven Hammarling, Numerical Algorithms Group Ltd.
183*> \endverbatim
184*>
185* =====================================================================
186 SUBROUTINE dgemm(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,
187 + BETA,C,LDC)
188*
189* -- Reference BLAS level3 routine --
190* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
191* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
192*
193* .. Scalar Arguments ..
194 DOUBLE PRECISION ALPHA,BETA
195 INTEGER K,LDA,LDB,LDC,M,N
196 CHARACTER TRANSA,TRANSB
197* ..
198* .. Array Arguments ..
199 DOUBLE PRECISION A(LDA,*),B(LDB,*),C(LDC,*)
200* ..
201*
202* =====================================================================
203*
204* .. External Functions ..
205 LOGICAL LSAME
206 EXTERNAL lsame
207* ..
208* .. External Subroutines ..
209 EXTERNAL xerbla
210* ..
211* .. Intrinsic Functions ..
212 INTRINSIC max
213* ..
214* .. Local Scalars ..
215 DOUBLE PRECISION TEMP
216 INTEGER I,INFO,J,L,NROWA,NROWB
217 LOGICAL NOTA,NOTB
218* ..
219* .. Parameters ..
220 DOUBLE PRECISION ONE,ZERO
221 parameter(one=1.0d+0,zero=0.0d+0)
222* ..
223*
224* Set NOTA and NOTB as true if A and B respectively are not
225* transposed and set NROWA and NROWB as the number of rows of A
226* and B respectively.
227*
228 nota = lsame(transa,'N')
229 notb = lsame(transb,'N')
230 IF (nota) THEN
231 nrowa = m
232 ELSE
233 nrowa = k
234 END IF
235 IF (notb) THEN
236 nrowb = k
237 ELSE
238 nrowb = n
239 END IF
240*
241* Test the input parameters.
242*
243 info = 0
244 IF ((.NOT.nota) .AND. (.NOT.lsame(transa,'C')) .AND.
245 + (.NOT.lsame(transa,'T'))) THEN
246 info = 1
247 ELSE IF ((.NOT.notb) .AND. (.NOT.lsame(transb,'C')) .AND.
248 + (.NOT.lsame(transb,'T'))) THEN
249 info = 2
250 ELSE IF (m.LT.0) THEN
251 info = 3
252 ELSE IF (n.LT.0) THEN
253 info = 4
254 ELSE IF (k.LT.0) THEN
255 info = 5
256 ELSE IF (lda.LT.max(1,nrowa)) THEN
257 info = 8
258 ELSE IF (ldb.LT.max(1,nrowb)) THEN
259 info = 10
260 ELSE IF (ldc.LT.max(1,m)) THEN
261 info = 13
262 END IF
263 IF (info.NE.0) THEN
264 CALL xerbla('DGEMM ',info)
265 RETURN
266 END IF
267*
268* Quick return if possible.
269*
270 IF ((m.EQ.0) .OR. (n.EQ.0) .OR.
271 + (((alpha.EQ.zero).OR. (k.EQ.0)).AND. (beta.EQ.one))) RETURN
272*
273* And if alpha.eq.zero.
274*
275 IF (alpha.EQ.zero) THEN
276 IF (beta.EQ.zero) THEN
277 DO 20 j = 1,n
278 DO 10 i = 1,m
279 c(i,j) = zero
280 10 CONTINUE
281 20 CONTINUE
282 ELSE
283 DO 40 j = 1,n
284 DO 30 i = 1,m
285 c(i,j) = beta*c(i,j)
286 30 CONTINUE
287 40 CONTINUE
288 END IF
289 RETURN
290 END IF
291*
292* Start the operations.
293*
294 IF (notb) THEN
295 IF (nota) THEN
296*
297* Form C := alpha*A*B + beta*C.
298*
299 DO 90 j = 1,n
300 IF (beta.EQ.zero) THEN
301 DO 50 i = 1,m
302 c(i,j) = zero
303 50 CONTINUE
304 ELSE IF (beta.NE.one) THEN
305 DO 60 i = 1,m
306 c(i,j) = beta*c(i,j)
307 60 CONTINUE
308 END IF
309 DO 80 l = 1,k
310 temp = alpha*b(l,j)
311 DO 70 i = 1,m
312 c(i,j) = c(i,j) + temp*a(i,l)
313 70 CONTINUE
314 80 CONTINUE
315 90 CONTINUE
316 ELSE
317*
318* Form C := alpha*A**T*B + beta*C
319*
320 DO 120 j = 1,n
321 DO 110 i = 1,m
322 temp = zero
323 DO 100 l = 1,k
324 temp = temp + a(l,i)*b(l,j)
325 100 CONTINUE
326 IF (beta.EQ.zero) THEN
327 c(i,j) = alpha*temp
328 ELSE
329 c(i,j) = alpha*temp + beta*c(i,j)
330 END IF
331 110 CONTINUE
332 120 CONTINUE
333 END IF
334 ELSE
335 IF (nota) THEN
336*
337* Form C := alpha*A*B**T + beta*C
338*
339 DO 170 j = 1,n
340 IF (beta.EQ.zero) THEN
341 DO 130 i = 1,m
342 c(i,j) = zero
343 130 CONTINUE
344 ELSE IF (beta.NE.one) THEN
345 DO 140 i = 1,m
346 c(i,j) = beta*c(i,j)
347 140 CONTINUE
348 END IF
349 DO 160 l = 1,k
350 temp = alpha*b(j,l)
351 DO 150 i = 1,m
352 c(i,j) = c(i,j) + temp*a(i,l)
353 150 CONTINUE
354 160 CONTINUE
355 170 CONTINUE
356 ELSE
357*
358* Form C := alpha*A**T*B**T + beta*C
359*
360 DO 200 j = 1,n
361 DO 190 i = 1,m
362 temp = zero
363 DO 180 l = 1,k
364 temp = temp + a(l,i)*b(j,l)
365 180 CONTINUE
366 IF (beta.EQ.zero) THEN
367 c(i,j) = alpha*temp
368 ELSE
369 c(i,j) = alpha*temp + beta*c(i,j)
370 END IF
371 190 CONTINUE
372 200 CONTINUE
373 END IF
374 END IF
375*
376 RETURN
377*
378* End of DGEMM
379*
380 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
DGEMM
Definition dgemm.f:188