LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine clatm6 ( integer  TYPE,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( lda, * )  B,
complex, dimension( ldx, * )  X,
integer  LDX,
complex, dimension( ldy, * )  Y,
integer  LDY,
complex  ALPHA,
complex  BETA,
complex  WX,
complex  WY,
real, dimension( * )  S,
real, dimension( * )  DIF 
)

CLATM6

Purpose:
 CLATM6 generates test matrices for the generalized eigenvalue
 problem, their corresponding right and left eigenvector matrices,
 and also reciprocal condition numbers for all eigenvalues and
 the reciprocal condition numbers of eigenvectors corresponding to
 the 1th and 5th eigenvalues.

 Test Matrices
 =============

 Two kinds of test matrix pairs
          (A, B) = inverse(YH) * (Da, Db) * inverse(X)
 are used in the tests:

 Type 1:
    Da = 1+a   0    0    0    0    Db = 1   0   0   0   0
          0   2+a   0    0    0         0   1   0   0   0
          0    0   3+a   0    0         0   0   1   0   0
          0    0    0   4+a   0         0   0   0   1   0
          0    0    0    0   5+a ,      0   0   0   0   1
 and Type 2:
    Da = 1+i   0    0       0       0    Db = 1   0   0   0   0
          0   1-i   0       0       0         0   1   0   0   0
          0    0    1       0       0         0   0   1   0   0
          0    0    0 (1+a)+(1+b)i  0         0   0   0   1   0
          0    0    0       0 (1+a)-(1+b)i,   0   0   0   0   1 .

 In both cases the same inverse(YH) and inverse(X) are used to compute
 (A, B), giving the exact eigenvectors to (A,B) as (YH, X):

 YH:  =  1    0   -y    y   -y    X =  1   0  -x  -x   x
         0    1   -y    y   -y         0   1   x  -x  -x
         0    0    1    0    0         0   0   1   0   0
         0    0    0    1    0         0   0   0   1   0
         0    0    0    0    1,        0   0   0   0   1 , where

 a, b, x and y will have all values independently of each other.
Parameters
[in]TYPE
          TYPE is INTEGER
          Specifies the problem type (see futher details).
[in]N
          N is INTEGER
          Size of the matrices A and B.
[out]A
          A is COMPLEX array, dimension (LDA, N).
          On exit A N-by-N is initialized according to TYPE.
[in]LDA
          LDA is INTEGER
          The leading dimension of A and of B.
[out]B
          B is COMPLEX array, dimension (LDA, N).
          On exit B N-by-N is initialized according to TYPE.
[out]X
          X is COMPLEX array, dimension (LDX, N).
          On exit X is the N-by-N matrix of right eigenvectors.
[in]LDX
          LDX is INTEGER
          The leading dimension of X.
[out]Y
          Y is COMPLEX array, dimension (LDY, N).
          On exit Y is the N-by-N matrix of left eigenvectors.
[in]LDY
          LDY is INTEGER
          The leading dimension of Y.
[in]ALPHA
          ALPHA is COMPLEX
[in]BETA
          BETA is COMPLEX

          Weighting constants for matrix A.
[in]WX
          WX is COMPLEX
          Constant for right eigenvector matrix.
[in]WY
          WY is COMPLEX
          Constant for left eigenvector matrix.
[out]S
          S is REAL array, dimension (N)
          S(i) is the reciprocal condition number for eigenvalue i.
[out]DIF
          DIF is REAL array, dimension (N)
          DIF(i) is the reciprocal condition number for eigenvector i.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 176 of file clatm6.f.

176 *
177 * -- LAPACK computational routine (version 3.4.0) --
178 * -- LAPACK is a software package provided by Univ. of Tennessee, --
179 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
180 * November 2011
181 *
182 * .. Scalar Arguments ..
183  INTEGER lda, ldx, ldy, n, type
184  COMPLEX alpha, beta, wx, wy
185 * ..
186 * .. Array Arguments ..
187  REAL dif( * ), s( * )
188  COMPLEX a( lda, * ), b( lda, * ), x( ldx, * ),
189  $ y( ldy, * )
190 * ..
191 *
192 * =====================================================================
193 *
194 * .. Parameters ..
195  REAL rone, two, three
196  parameter ( rone = 1.0e+0, two = 2.0e+0, three = 3.0e+0 )
197  COMPLEX zero, one
198  parameter ( zero = ( 0.0e+0, 0.0e+0 ),
199  $ one = ( 1.0e+0, 0.0e+0 ) )
200 * ..
201 * .. Local Scalars ..
202  INTEGER i, info, j
203 * ..
204 * .. Local Arrays ..
205  REAL rwork( 50 )
206  COMPLEX work( 26 ), z( 8, 8 )
207 * ..
208 * .. Intrinsic Functions ..
209  INTRINSIC cabs, cmplx, conjg, REAL, sqrt
210 * ..
211 * .. External Subroutines ..
212  EXTERNAL cgesvd, clacpy, clakf2
213 * ..
214 * .. Executable Statements ..
215 *
216 * Generate test problem ...
217 * (Da, Db) ...
218 *
219  DO 20 i = 1, n
220  DO 10 j = 1, n
221 *
222  IF( i.EQ.j ) THEN
223  a( i, i ) = cmplx( i ) + alpha
224  b( i, i ) = one
225  ELSE
226  a( i, j ) = zero
227  b( i, j ) = zero
228  END IF
229 *
230  10 CONTINUE
231  20 CONTINUE
232  IF( type.EQ.2 ) THEN
233  a( 1, 1 ) = cmplx( rone, rone )
234  a( 2, 2 ) = conjg( a( 1, 1 ) )
235  a( 3, 3 ) = one
236  a( 4, 4 ) = cmplx( REAL( ONE+ALPHA ), REAL( ONE+BETA ) )
237  a( 5, 5 ) = conjg( a( 4, 4 ) )
238  END IF
239 *
240 * Form X and Y
241 *
242  CALL clacpy( 'F', n, n, b, lda, y, ldy )
243  y( 3, 1 ) = -conjg( wy )
244  y( 4, 1 ) = conjg( wy )
245  y( 5, 1 ) = -conjg( wy )
246  y( 3, 2 ) = -conjg( wy )
247  y( 4, 2 ) = conjg( wy )
248  y( 5, 2 ) = -conjg( wy )
249 *
250  CALL clacpy( 'F', n, n, b, lda, x, ldx )
251  x( 1, 3 ) = -wx
252  x( 1, 4 ) = -wx
253  x( 1, 5 ) = wx
254  x( 2, 3 ) = wx
255  x( 2, 4 ) = -wx
256  x( 2, 5 ) = -wx
257 *
258 * Form (A, B)
259 *
260  b( 1, 3 ) = wx + wy
261  b( 2, 3 ) = -wx + wy
262  b( 1, 4 ) = wx - wy
263  b( 2, 4 ) = wx - wy
264  b( 1, 5 ) = -wx + wy
265  b( 2, 5 ) = wx + wy
266  a( 1, 3 ) = wx*a( 1, 1 ) + wy*a( 3, 3 )
267  a( 2, 3 ) = -wx*a( 2, 2 ) + wy*a( 3, 3 )
268  a( 1, 4 ) = wx*a( 1, 1 ) - wy*a( 4, 4 )
269  a( 2, 4 ) = wx*a( 2, 2 ) - wy*a( 4, 4 )
270  a( 1, 5 ) = -wx*a( 1, 1 ) + wy*a( 5, 5 )
271  a( 2, 5 ) = wx*a( 2, 2 ) + wy*a( 5, 5 )
272 *
273 * Compute condition numbers
274 *
275  s( 1 ) = rone / sqrt( ( rone+three*cabs( wy )*cabs( wy ) ) /
276  $ ( rone+cabs( a( 1, 1 ) )*cabs( a( 1, 1 ) ) ) )
277  s( 2 ) = rone / sqrt( ( rone+three*cabs( wy )*cabs( wy ) ) /
278  $ ( rone+cabs( a( 2, 2 ) )*cabs( a( 2, 2 ) ) ) )
279  s( 3 ) = rone / sqrt( ( rone+two*cabs( wx )*cabs( wx ) ) /
280  $ ( rone+cabs( a( 3, 3 ) )*cabs( a( 3, 3 ) ) ) )
281  s( 4 ) = rone / sqrt( ( rone+two*cabs( wx )*cabs( wx ) ) /
282  $ ( rone+cabs( a( 4, 4 ) )*cabs( a( 4, 4 ) ) ) )
283  s( 5 ) = rone / sqrt( ( rone+two*cabs( wx )*cabs( wx ) ) /
284  $ ( rone+cabs( a( 5, 5 ) )*cabs( a( 5, 5 ) ) ) )
285 *
286  CALL clakf2( 1, 4, a, lda, a( 2, 2 ), b, b( 2, 2 ), z, 8 )
287  CALL cgesvd( 'N', 'N', 8, 8, z, 8, rwork, work, 1, work( 2 ), 1,
288  $ work( 3 ), 24, rwork( 9 ), info )
289  dif( 1 ) = rwork( 8 )
290 *
291  CALL clakf2( 4, 1, a, lda, a( 5, 5 ), b, b( 5, 5 ), z, 8 )
292  CALL cgesvd( 'N', 'N', 8, 8, z, 8, rwork, work, 1, work( 2 ), 1,
293  $ work( 3 ), 24, rwork( 9 ), info )
294  dif( 5 ) = rwork( 8 )
295 *
296  RETURN
297 *
298 * End of CLATM6
299 *
subroutine cgesvd(JOBU, JOBVT, M, N, A, LDA, S, U, LDU, VT, LDVT, WORK, LWORK, RWORK, INFO)
CGESVD computes the singular value decomposition (SVD) for GE matrices
Definition: cgesvd.f:216
subroutine clakf2(M, N, A, LDA, B, D, E, Z, LDZ)
CLAKF2
Definition: clakf2.f:107
subroutine clacpy(UPLO, M, N, A, LDA, B, LDB)
CLACPY copies all or part of one two-dimensional array to another.
Definition: clacpy.f:105

Here is the call graph for this function:

Here is the caller graph for this function: