LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlakf2.f
Go to the documentation of this file.
1*> \brief \b DLAKF2
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 DLAKF2( M, N, A, LDA, B, D, E, Z, LDZ )
12*
13* .. Scalar Arguments ..
14* INTEGER LDA, LDZ, M, N
15* ..
16* .. Array Arguments ..
17* DOUBLE PRECISION A( LDA, * ), B( LDA, * ), D( LDA, * ),
18* $ E( LDA, * ), Z( LDZ, * )
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> Form the 2*M*N by 2*M*N matrix
28*>
29*> Z = [ kron(In, A) -kron(B', Im) ]
30*> [ kron(In, D) -kron(E', Im) ],
31*>
32*> where In is the identity matrix of size n and X' is the transpose
33*> of X. kron(X, Y) is the Kronecker product between the matrices X
34*> and Y.
35*> \endverbatim
36*
37* Arguments:
38* ==========
39*
40*> \param[in] M
41*> \verbatim
42*> M is INTEGER
43*> Size of matrix, must be >= 1.
44*> \endverbatim
45*>
46*> \param[in] N
47*> \verbatim
48*> N is INTEGER
49*> Size of matrix, must be >= 1.
50*> \endverbatim
51*>
52*> \param[in] A
53*> \verbatim
54*> A is DOUBLE PRECISION, dimension ( LDA, M )
55*> The matrix A in the output matrix Z.
56*> \endverbatim
57*>
58*> \param[in] LDA
59*> \verbatim
60*> LDA is INTEGER
61*> The leading dimension of A, B, D, and E. ( LDA >= M+N )
62*> \endverbatim
63*>
64*> \param[in] B
65*> \verbatim
66*> B is DOUBLE PRECISION, dimension ( LDA, N )
67*> \endverbatim
68*>
69*> \param[in] D
70*> \verbatim
71*> D is DOUBLE PRECISION, dimension ( LDA, M )
72*> \endverbatim
73*>
74*> \param[in] E
75*> \verbatim
76*> E is DOUBLE PRECISION, dimension ( LDA, N )
77*>
78*> The matrices used in forming the output matrix Z.
79*> \endverbatim
80*>
81*> \param[out] Z
82*> \verbatim
83*> Z is DOUBLE PRECISION, dimension ( LDZ, 2*M*N )
84*> The resultant Kronecker M*N*2 by M*N*2 matrix (see above.)
85*> \endverbatim
86*>
87*> \param[in] LDZ
88*> \verbatim
89*> LDZ is INTEGER
90*> The leading dimension of Z. ( LDZ >= 2*M*N )
91*> \endverbatim
92*
93* Authors:
94* ========
95*
96*> \author Univ. of Tennessee
97*> \author Univ. of California Berkeley
98*> \author Univ. of Colorado Denver
99*> \author NAG Ltd.
100*
101*> \ingroup double_matgen
102*
103* =====================================================================
104 SUBROUTINE dlakf2( M, N, A, LDA, B, D, E, Z, LDZ )
105*
106* -- LAPACK computational routine --
107* -- LAPACK is a software package provided by Univ. of Tennessee, --
108* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
109*
110* .. Scalar Arguments ..
111 INTEGER LDA, LDZ, M, N
112* ..
113* .. Array Arguments ..
114 DOUBLE PRECISION A( LDA, * ), B( LDA, * ), D( LDA, * ),
115 $ E( LDA, * ), Z( LDZ, * )
116* ..
117*
118* ====================================================================
119*
120* .. Parameters ..
121 DOUBLE PRECISION ZERO
122 parameter( zero = 0.0d+0 )
123* ..
124* .. Local Scalars ..
125 INTEGER I, IK, J, JK, L, MN, MN2
126* ..
127* .. External Subroutines ..
128 EXTERNAL dlaset
129* ..
130* .. Executable Statements ..
131*
132* Initialize Z
133*
134 mn = m*n
135 mn2 = 2*mn
136 CALL dlaset( 'Full', mn2, mn2, zero, zero, z, ldz )
137*
138 ik = 1
139 DO 50 l = 1, n
140*
141* form kron(In, A)
142*
143 DO 20 i = 1, m
144 DO 10 j = 1, m
145 z( ik+i-1, ik+j-1 ) = a( i, j )
146 10 CONTINUE
147 20 CONTINUE
148*
149* form kron(In, D)
150*
151 DO 40 i = 1, m
152 DO 30 j = 1, m
153 z( ik+mn+i-1, ik+j-1 ) = d( i, j )
154 30 CONTINUE
155 40 CONTINUE
156*
157 ik = ik + m
158 50 CONTINUE
159*
160 ik = 1
161 DO 90 l = 1, n
162 jk = mn + 1
163*
164 DO 80 j = 1, n
165*
166* form -kron(B', Im)
167*
168 DO 60 i = 1, m
169 z( ik+i-1, jk+i-1 ) = -b( j, l )
170 60 CONTINUE
171*
172* form -kron(E', Im)
173*
174 DO 70 i = 1, m
175 z( ik+mn+i-1, jk+i-1 ) = -e( j, l )
176 70 CONTINUE
177*
178 jk = jk + m
179 80 CONTINUE
180*
181 ik = ik + m
182 90 CONTINUE
183*
184 RETURN
185*
186* End of DLAKF2
187*
188 END
subroutine dlakf2(m, n, a, lda, b, d, e, z, ldz)
DLAKF2
Definition dlakf2.f:105
subroutine dlaset(uplo, m, n, alpha, beta, a, lda)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition dlaset.f:110