LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine clatm4 ( integer  ITYPE,
integer  N,
integer  NZ1,
integer  NZ2,
logical  RSIGN,
real  AMAGN,
real  RCOND,
real  TRIANG,
integer  IDIST,
integer, dimension( 4 )  ISEED,
complex, dimension( lda, * )  A,
integer  LDA 
)

CLATM4

Purpose:
 CLATM4 generates basic square matrices, which may later be
 multiplied by others in order to produce test matrices.  It is
 intended mainly to be used to test the generalized eigenvalue
 routines.

 It first generates the diagonal and (possibly) subdiagonal,
 according to the value of ITYPE, NZ1, NZ2, RSIGN, AMAGN, and RCOND.
 It then fills in the upper triangle with random numbers, if TRIANG is
 non-zero.
Parameters
[in]ITYPE
          ITYPE is INTEGER
          The "type" of matrix on the diagonal and sub-diagonal.
          If ITYPE < 0, then type abs(ITYPE) is generated and then
             swapped end for end (A(I,J) := A'(N-J,N-I).)  See also
             the description of AMAGN and RSIGN.

          Special types:
          = 0:  the zero matrix.
          = 1:  the identity.
          = 2:  a transposed Jordan block.
          = 3:  If N is odd, then a k+1 x k+1 transposed Jordan block
                followed by a k x k identity block, where k=(N-1)/2.
                If N is even, then k=(N-2)/2, and a zero diagonal entry
                is tacked onto the end.

          Diagonal types.  The diagonal consists of NZ1 zeros, then
             k=N-NZ1-NZ2 nonzeros.  The subdiagonal is zero.  ITYPE
             specifies the nonzero diagonal entries as follows:
          = 4:  1, ..., k
          = 5:  1, RCOND, ..., RCOND
          = 6:  1, ..., 1, RCOND
          = 7:  1, a, a^2, ..., a^(k-1)=RCOND
          = 8:  1, 1-d, 1-2*d, ..., 1-(k-1)*d=RCOND
          = 9:  random numbers chosen from (RCOND,1)
          = 10: random numbers with distribution IDIST (see CLARND.)
[in]N
          N is INTEGER
          The order of the matrix.
[in]NZ1
          NZ1 is INTEGER
          If abs(ITYPE) > 3, then the first NZ1 diagonal entries will
          be zero.
[in]NZ2
          NZ2 is INTEGER
          If abs(ITYPE) > 3, then the last NZ2 diagonal entries will
          be zero.
[in]RSIGN
          RSIGN is LOGICAL
          = .TRUE.:  The diagonal and subdiagonal entries will be
                     multiplied by random numbers of magnitude 1.
          = .FALSE.: The diagonal and subdiagonal entries will be
                     left as they are (usually non-negative real.)
[in]AMAGN
          AMAGN is REAL
          The diagonal and subdiagonal entries will be multiplied by
          AMAGN.
[in]RCOND
          RCOND is REAL
          If abs(ITYPE) > 4, then the smallest diagonal entry will be
          RCOND.  RCOND must be between 0 and 1.
[in]TRIANG
          TRIANG is REAL
          The entries above the diagonal will be random numbers with
          magnitude bounded by TRIANG (i.e., random numbers multiplied
          by TRIANG.)
[in]IDIST
          IDIST is INTEGER
          On entry, DIST specifies the type of distribution to be used
          to generate a random matrix .
          = 1: real and imaginary parts each UNIFORM( 0, 1 )
          = 2: real and imaginary parts each UNIFORM( -1, 1 )
          = 3: real and imaginary parts each NORMAL( 0, 1 )
          = 4: complex number uniform in DISK( 0, 1 )
[in,out]ISEED
          ISEED is INTEGER array, dimension (4)
          On entry ISEED specifies the seed of the random number
          generator.  The values of ISEED are changed on exit, and can
          be used in the next call to CLATM4 to continue the same
          random number sequence.
          Note: ISEED(4) should be odd, for the random number generator
          used at present.
[out]A
          A is COMPLEX array, dimension (LDA, N)
          Array to be computed.
[in]LDA
          LDA is INTEGER
          Leading dimension of A.  Must be at least 1 and at least N.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 173 of file clatm4.f.

173 *
174 * -- LAPACK test routine (version 3.4.0) --
175 * -- LAPACK is a software package provided by Univ. of Tennessee, --
176 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
177 * November 2011
178 *
179 * .. Scalar Arguments ..
180  LOGICAL rsign
181  INTEGER idist, itype, lda, n, nz1, nz2
182  REAL amagn, rcond, triang
183 * ..
184 * .. Array Arguments ..
185  INTEGER iseed( 4 )
186  COMPLEX a( lda, * )
187 * ..
188 *
189 * =====================================================================
190 *
191 * .. Parameters ..
192  REAL zero, one
193  parameter ( zero = 0.0e+0, one = 1.0e+0 )
194  COMPLEX czero, cone
195  parameter ( czero = ( 0.0e+0, 0.0e+0 ),
196  $ cone = ( 1.0e+0, 0.0e+0 ) )
197 * ..
198 * .. Local Scalars ..
199  INTEGER i, isdb, isde, jc, jd, jr, k, kbeg, kend, klen
200  REAL alpha
201  COMPLEX ctemp
202 * ..
203 * .. External Functions ..
204  REAL slaran
205  COMPLEX clarnd
206  EXTERNAL slaran, clarnd
207 * ..
208 * .. External Subroutines ..
209  EXTERNAL claset
210 * ..
211 * .. Intrinsic Functions ..
212  INTRINSIC abs, cmplx, exp, log, max, min, mod, real
213 * ..
214 * .. Executable Statements ..
215 *
216  IF( n.LE.0 )
217  $ RETURN
218  CALL claset( 'Full', n, n, czero, czero, a, lda )
219 *
220 * Insure a correct ISEED
221 *
222  IF( mod( iseed( 4 ), 2 ).NE.1 )
223  $ iseed( 4 ) = iseed( 4 ) + 1
224 *
225 * Compute diagonal and subdiagonal according to ITYPE, NZ1, NZ2,
226 * and RCOND
227 *
228  IF( itype.NE.0 ) THEN
229  IF( abs( itype ).GE.4 ) THEN
230  kbeg = max( 1, min( n, nz1+1 ) )
231  kend = max( kbeg, min( n, n-nz2 ) )
232  klen = kend + 1 - kbeg
233  ELSE
234  kbeg = 1
235  kend = n
236  klen = n
237  END IF
238  isdb = 1
239  isde = 0
240  GO TO ( 10, 30, 50, 80, 100, 120, 140, 160,
241  $ 180, 200 )abs( itype )
242 *
243 * abs(ITYPE) = 1: Identity
244 *
245  10 CONTINUE
246  DO 20 jd = 1, n
247  a( jd, jd ) = cone
248  20 CONTINUE
249  GO TO 220
250 *
251 * abs(ITYPE) = 2: Transposed Jordan block
252 *
253  30 CONTINUE
254  DO 40 jd = 1, n - 1
255  a( jd+1, jd ) = cone
256  40 CONTINUE
257  isdb = 1
258  isde = n - 1
259  GO TO 220
260 *
261 * abs(ITYPE) = 3: Transposed Jordan block, followed by the
262 * identity.
263 *
264  50 CONTINUE
265  k = ( n-1 ) / 2
266  DO 60 jd = 1, k
267  a( jd+1, jd ) = cone
268  60 CONTINUE
269  isdb = 1
270  isde = k
271  DO 70 jd = k + 2, 2*k + 1
272  a( jd, jd ) = cone
273  70 CONTINUE
274  GO TO 220
275 *
276 * abs(ITYPE) = 4: 1,...,k
277 *
278  80 CONTINUE
279  DO 90 jd = kbeg, kend
280  a( jd, jd ) = cmplx( jd-nz1 )
281  90 CONTINUE
282  GO TO 220
283 *
284 * abs(ITYPE) = 5: One large D value:
285 *
286  100 CONTINUE
287  DO 110 jd = kbeg + 1, kend
288  a( jd, jd ) = cmplx( rcond )
289  110 CONTINUE
290  a( kbeg, kbeg ) = cone
291  GO TO 220
292 *
293 * abs(ITYPE) = 6: One small D value:
294 *
295  120 CONTINUE
296  DO 130 jd = kbeg, kend - 1
297  a( jd, jd ) = cone
298  130 CONTINUE
299  a( kend, kend ) = cmplx( rcond )
300  GO TO 220
301 *
302 * abs(ITYPE) = 7: Exponentially distributed D values:
303 *
304  140 CONTINUE
305  a( kbeg, kbeg ) = cone
306  IF( klen.GT.1 ) THEN
307  alpha = rcond**( one / REAL( KLEN-1 ) )
308  DO 150 i = 2, klen
309  a( nz1+i, nz1+i ) = cmplx( alpha**REAL( I-1 ) )
310  150 CONTINUE
311  END IF
312  GO TO 220
313 *
314 * abs(ITYPE) = 8: Arithmetically distributed D values:
315 *
316  160 CONTINUE
317  a( kbeg, kbeg ) = cone
318  IF( klen.GT.1 ) THEN
319  alpha = ( one-rcond ) / REAL( klen-1 )
320  DO 170 i = 2, klen
321  a( nz1+i, nz1+i ) = cmplx( REAL( klen-i )*alpha+rcond )
322  170 CONTINUE
323  END IF
324  GO TO 220
325 *
326 * abs(ITYPE) = 9: Randomly distributed D values on ( RCOND, 1):
327 *
328  180 CONTINUE
329  alpha = log( rcond )
330  DO 190 jd = kbeg, kend
331  a( jd, jd ) = exp( alpha*slaran( iseed ) )
332  190 CONTINUE
333  GO TO 220
334 *
335 * abs(ITYPE) = 10: Randomly distributed D values from DIST
336 *
337  200 CONTINUE
338  DO 210 jd = kbeg, kend
339  a( jd, jd ) = clarnd( idist, iseed )
340  210 CONTINUE
341 *
342  220 CONTINUE
343 *
344 * Scale by AMAGN
345 *
346  DO 230 jd = kbeg, kend
347  a( jd, jd ) = amagn*REAL( A( JD, JD ) )
348  230 CONTINUE
349  DO 240 jd = isdb, isde
350  a( jd+1, jd ) = amagn*REAL( A( JD+1, JD ) )
351  240 CONTINUE
352 *
353 * If RSIGN = .TRUE., assign random signs to diagonal and
354 * subdiagonal
355 *
356  IF( rsign ) THEN
357  DO 250 jd = kbeg, kend
358  IF( REAL( A( JD, JD ) ).NE.zero ) then
359  ctemp = clarnd( 3, iseed )
360  ctemp = ctemp / abs( ctemp )
361  a( jd, jd ) = ctemp*REAL( A( JD, JD ) )
362  END IF
363  250 CONTINUE
364  DO 260 jd = isdb, isde
365  IF( REAL( A( JD+1, JD ) ).NE.zero ) then
366  ctemp = clarnd( 3, iseed )
367  ctemp = ctemp / abs( ctemp )
368  a( jd+1, jd ) = ctemp*REAL( A( JD+1, JD ) )
369  END IF
370  260 CONTINUE
371  END IF
372 *
373 * Reverse if ITYPE < 0
374 *
375  IF( itype.LT.0 ) THEN
376  DO 270 jd = kbeg, ( kbeg+kend-1 ) / 2
377  ctemp = a( jd, jd )
378  a( jd, jd ) = a( kbeg+kend-jd, kbeg+kend-jd )
379  a( kbeg+kend-jd, kbeg+kend-jd ) = ctemp
380  270 CONTINUE
381  DO 280 jd = 1, ( n-1 ) / 2
382  ctemp = a( jd+1, jd )
383  a( jd+1, jd ) = a( n+1-jd, n-jd )
384  a( n+1-jd, n-jd ) = ctemp
385  280 CONTINUE
386  END IF
387 *
388  END IF
389 *
390 * Fill in upper triangle
391 *
392  IF( triang.NE.zero ) THEN
393  DO 300 jc = 2, n
394  DO 290 jr = 1, jc - 1
395  a( jr, jc ) = triang*clarnd( idist, iseed )
396  290 CONTINUE
397  300 CONTINUE
398  END IF
399 *
400  RETURN
401 *
402 * End of CLATM4
403 *
complex function clarnd(IDIST, ISEED)
CLARND
Definition: clarnd.f:77
subroutine claset(UPLO, M, N, ALPHA, BETA, A, LDA)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: claset.f:108
real function slaran(ISEED)
SLARAN
Definition: slaran.f:69

Here is the call graph for this function:

Here is the caller graph for this function: