LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zlakf2.f
Go to the documentation of this file.
1 *> \brief \b ZLAKF2
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 ZLAKF2( M, N, A, LDA, B, D, E, Z, LDZ )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER LDA, LDZ, M, N
15 * ..
16 * .. Array Arguments ..
17 * COMPLEX*16 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 COMPLEX*16, 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 COMPLEX*16, dimension ( LDA, N )
67 *> \endverbatim
68 *>
69 *> \param[in] D
70 *> \verbatim
71 *> D is COMPLEX*16, dimension ( LDA, M )
72 *> \endverbatim
73 *>
74 *> \param[in] E
75 *> \verbatim
76 *> E is COMPLEX*16, 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 COMPLEX*16, 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 *> \date November 2011
102 *
103 *> \ingroup complex16_matgen
104 *
105 * =====================================================================
106  SUBROUTINE zlakf2( M, N, A, LDA, B, D, E, Z, LDZ )
107 *
108 * -- LAPACK computational routine (version 3.4.0) --
109 * -- LAPACK is a software package provided by Univ. of Tennessee, --
110 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
111 * November 2011
112 *
113 * .. Scalar Arguments ..
114  INTEGER lda, ldz, m, n
115 * ..
116 * .. Array Arguments ..
117  COMPLEX*16 a( lda, * ), b( lda, * ), d( lda, * ),
118  $ e( lda, * ), z( ldz, * )
119 * ..
120 *
121 * ====================================================================
122 *
123 * .. Parameters ..
124  COMPLEX*16 zero
125  parameter( zero = ( 0.0d+0, 0.0d+0 ) )
126 * ..
127 * .. Local Scalars ..
128  INTEGER i, ik, j, jk, l, mn, mn2
129 * ..
130 * .. External Subroutines ..
131  EXTERNAL zlaset
132 * ..
133 * .. Executable Statements ..
134 *
135 * Initialize Z
136 *
137  mn = m*n
138  mn2 = 2*mn
139  CALL zlaset( 'Full', mn2, mn2, zero, zero, z, ldz )
140 *
141  ik = 1
142  DO 50 l = 1, n
143 *
144 * form kron(In, A)
145 *
146  DO 20 i = 1, m
147  DO 10 j = 1, m
148  z( ik+i-1, ik+j-1 ) = a( i, j )
149  10 continue
150  20 continue
151 *
152 * form kron(In, D)
153 *
154  DO 40 i = 1, m
155  DO 30 j = 1, m
156  z( ik+mn+i-1, ik+j-1 ) = d( i, j )
157  30 continue
158  40 continue
159 *
160  ik = ik + m
161  50 continue
162 *
163  ik = 1
164  DO 90 l = 1, n
165  jk = mn + 1
166 *
167  DO 80 j = 1, n
168 *
169 * form -kron(B', Im)
170 *
171  DO 60 i = 1, m
172  z( ik+i-1, jk+i-1 ) = -b( j, l )
173  60 continue
174 *
175 * form -kron(E', Im)
176 *
177  DO 70 i = 1, m
178  z( ik+mn+i-1, jk+i-1 ) = -e( j, l )
179  70 continue
180 *
181  jk = jk + m
182  80 continue
183 *
184  ik = ik + m
185  90 continue
186 *
187  return
188 *
189 * End of ZLAKF2
190 *
191  END