LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zlacrm.f
Go to the documentation of this file.
1 *> \brief \b ZLACRM multiplies a complex matrix by a square real matrix.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZLACRM + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlacrm.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlacrm.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacrm.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZLACRM( M, N, A, LDA, B, LDB, C, LDC, RWORK )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER LDA, LDB, LDC, M, N
25 * ..
26 * .. Array Arguments ..
27 * DOUBLE PRECISION B( LDB, * ), RWORK( * )
28 * COMPLEX*16 A( LDA, * ), C( LDC, * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> ZLACRM performs a very simple matrix-matrix multiplication:
38 *> C := A * B,
39 *> where A is M by N and complex; B is N by N and real;
40 *> C is M by N and complex.
41 *> \endverbatim
42 *
43 * Arguments:
44 * ==========
45 *
46 *> \param[in] M
47 *> \verbatim
48 *> M is INTEGER
49 *> The number of rows of the matrix A and of the matrix C.
50 *> M >= 0.
51 *> \endverbatim
52 *>
53 *> \param[in] N
54 *> \verbatim
55 *> N is INTEGER
56 *> The number of columns and rows of the matrix B and
57 *> the number of columns of the matrix C.
58 *> N >= 0.
59 *> \endverbatim
60 *>
61 *> \param[in] A
62 *> \verbatim
63 *> A is COMPLEX*16 array, dimension (LDA, N)
64 *> A contains the M by N matrix A.
65 *> \endverbatim
66 *>
67 *> \param[in] LDA
68 *> \verbatim
69 *> LDA is INTEGER
70 *> The leading dimension of the array A. LDA >=max(1,M).
71 *> \endverbatim
72 *>
73 *> \param[in] B
74 *> \verbatim
75 *> B is DOUBLE PRECISION array, dimension (LDB, N)
76 *> B contains the N by N matrix B.
77 *> \endverbatim
78 *>
79 *> \param[in] LDB
80 *> \verbatim
81 *> LDB is INTEGER
82 *> The leading dimension of the array B. LDB >=max(1,N).
83 *> \endverbatim
84 *>
85 *> \param[in] C
86 *> \verbatim
87 *> C is COMPLEX*16 array, dimension (LDC, N)
88 *> C contains the M by N matrix C.
89 *> \endverbatim
90 *>
91 *> \param[in] LDC
92 *> \verbatim
93 *> LDC is INTEGER
94 *> The leading dimension of the array C. LDC >=max(1,N).
95 *> \endverbatim
96 *>
97 *> \param[out] RWORK
98 *> \verbatim
99 *> RWORK is DOUBLE PRECISION array, dimension (2*M*N)
100 *> \endverbatim
101 *
102 * Authors:
103 * ========
104 *
105 *> \author Univ. of Tennessee
106 *> \author Univ. of California Berkeley
107 *> \author Univ. of Colorado Denver
108 *> \author NAG Ltd.
109 *
110 *> \date September 2012
111 *
112 *> \ingroup complex16OTHERauxiliary
113 *
114 * =====================================================================
115  SUBROUTINE zlacrm( M, N, A, LDA, B, LDB, C, LDC, RWORK )
116 *
117 * -- LAPACK auxiliary routine (version 3.4.2) --
118 * -- LAPACK is a software package provided by Univ. of Tennessee, --
119 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120 * September 2012
121 *
122 * .. Scalar Arguments ..
123  INTEGER lda, ldb, ldc, m, n
124 * ..
125 * .. Array Arguments ..
126  DOUBLE PRECISION b( ldb, * ), rwork( * )
127  COMPLEX*16 a( lda, * ), c( ldc, * )
128 * ..
129 *
130 * =====================================================================
131 *
132 * .. Parameters ..
133  DOUBLE PRECISION one, zero
134  parameter( one = 1.0d0, zero = 0.0d0 )
135 * ..
136 * .. Local Scalars ..
137  INTEGER i, j, l
138 * ..
139 * .. Intrinsic Functions ..
140  INTRINSIC dble, dcmplx, dimag
141 * ..
142 * .. External Subroutines ..
143  EXTERNAL dgemm
144 * ..
145 * .. Executable Statements ..
146 *
147 * Quick return if possible.
148 *
149  IF( ( m.EQ.0 ) .OR. ( n.EQ.0 ) )
150  $ return
151 *
152  DO 20 j = 1, n
153  DO 10 i = 1, m
154  rwork( ( j-1 )*m+i ) = dble( a( i, j ) )
155  10 continue
156  20 continue
157 *
158  l = m*n + 1
159  CALL dgemm( 'N', 'N', m, n, n, one, rwork, m, b, ldb, zero,
160  $ rwork( l ), m )
161  DO 40 j = 1, n
162  DO 30 i = 1, m
163  c( i, j ) = rwork( l+( j-1 )*m+i-1 )
164  30 continue
165  40 continue
166 *
167  DO 60 j = 1, n
168  DO 50 i = 1, m
169  rwork( ( j-1 )*m+i ) = dimag( a( i, j ) )
170  50 continue
171  60 continue
172  CALL dgemm( 'N', 'N', m, n, n, one, rwork, m, b, ldb, zero,
173  $ rwork( l ), m )
174  DO 80 j = 1, n
175  DO 70 i = 1, m
176  c( i, j ) = dcmplx( dble( c( i, j ) ),
177  $ rwork( l+( j-1 )*m+i-1 ) )
178  70 continue
179  80 continue
180 *
181  return
182 *
183 * End of ZLACRM
184 *
185  END