1*> \brief \b SLATM4
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 SLATM4( ITYPE, N, NZ1, NZ2, ISIGN, AMAGN, RCOND,
12*                          TRIANG, IDIST, ISEED, A, LDA )
13*
14*       .. Scalar Arguments ..
15*       INTEGER            IDIST, ISIGN, ITYPE, LDA, N, NZ1, NZ2
16*       REAL               AMAGN, RCOND, TRIANG
17*       ..
18*       .. Array Arguments ..
19*       INTEGER            ISEED( 4 )
20*       REAL               A( LDA, * )
21*       ..
22*
23*
24*> \par Purpose:
25*  =============
26*>
27*> \verbatim
28*>
29*> SLATM4 generates basic square matrices, which may later be
30*> multiplied by others in order to produce test matrices.  It is
31*> intended mainly to be used to test the generalized eigenvalue
32*> routines.
33*>
34*> It first generates the diagonal and (possibly) subdiagonal,
35*> according to the value of ITYPE, NZ1, NZ2, ISIGN, AMAGN, and RCOND.
36*> It then fills in the upper triangle with random numbers, if TRIANG is
37*> non-zero.
38*> \endverbatim
39*
40*  Arguments:
41*  ==========
42*
43*> \param[in] ITYPE
44*> \verbatim
45*>          ITYPE is INTEGER
46*>          The "type" of matrix on the diagonal and sub-diagonal.
47*>          If ITYPE < 0, then type abs(ITYPE) is generated and then
48*>             swapped end for end (A(I,J) := A'(N-J,N-I).)  See also
49*>             the description of AMAGN and ISIGN.
50*>
51*>          Special types:
52*>          = 0:  the zero matrix.
53*>          = 1:  the identity.
54*>          = 2:  a transposed Jordan block.
55*>          = 3:  If N is odd, then a k+1 x k+1 transposed Jordan block
56*>                followed by a k x k identity block, where k=(N-1)/2.
57*>                If N is even, then k=(N-2)/2, and a zero diagonal entry
58*>                is tacked onto the end.
59*>
60*>          Diagonal types.  The diagonal consists of NZ1 zeros, then
61*>             k=N-NZ1-NZ2 nonzeros.  The subdiagonal is zero.  ITYPE
62*>             specifies the nonzero diagonal entries as follows:
63*>          = 4:  1, ..., k
64*>          = 5:  1, RCOND, ..., RCOND
65*>          = 6:  1, ..., 1, RCOND
66*>          = 7:  1, a, a^2, ..., a^(k-1)=RCOND
67*>          = 8:  1, 1-d, 1-2*d, ..., 1-(k-1)*d=RCOND
68*>          = 9:  random numbers chosen from (RCOND,1)
69*>          = 10: random numbers with distribution IDIST (see SLARND.)
70*> \endverbatim
71*>
72*> \param[in] N
73*> \verbatim
74*>          N is INTEGER
75*>          The order of the matrix.
76*> \endverbatim
77*>
78*> \param[in] NZ1
79*> \verbatim
80*>          NZ1 is INTEGER
81*>          If abs(ITYPE) > 3, then the first NZ1 diagonal entries will
82*>          be zero.
83*> \endverbatim
84*>
85*> \param[in] NZ2
86*> \verbatim
87*>          NZ2 is INTEGER
88*>          If abs(ITYPE) > 3, then the last NZ2 diagonal entries will
89*>          be zero.
90*> \endverbatim
91*>
92*> \param[in] ISIGN
93*> \verbatim
94*>          ISIGN is INTEGER
95*>          = 0: The sign of the diagonal and subdiagonal entries will
96*>               be left unchanged.
97*>          = 1: The diagonal and subdiagonal entries will have their
98*>               sign changed at random.
99*>          = 2: If ITYPE is 2 or 3, then the same as ISIGN=1.
100*>               Otherwise, with probability 0.5, odd-even pairs of
101*>               diagonal entries A(2*j-1,2*j-1), A(2*j,2*j) will be
102*>               converted to a 2x2 block by pre- and post-multiplying
103*>               by distinct random orthogonal rotations.  The remaining
104*>               diagonal entries will have their sign changed at random.
105*> \endverbatim
106*>
107*> \param[in] AMAGN
108*> \verbatim
109*>          AMAGN is REAL
110*>          The diagonal and subdiagonal entries will be multiplied by
111*>          AMAGN.
112*> \endverbatim
113*>
114*> \param[in] RCOND
115*> \verbatim
116*>          RCOND is REAL
117*>          If abs(ITYPE) > 4, then the smallest diagonal entry will be
118*>          entry will be RCOND.  RCOND must be between 0 and 1.
119*> \endverbatim
120*>
121*> \param[in] TRIANG
122*> \verbatim
123*>          TRIANG is REAL
124*>          The entries above the diagonal will be random numbers with
125*>          magnitude bounded by TRIANG (i.e., random numbers multiplied
126*>          by TRIANG.)
127*> \endverbatim
128*>
129*> \param[in] IDIST
130*> \verbatim
131*>          IDIST is INTEGER
132*>          Specifies the type of distribution to be used to generate a
133*>          random matrix.
134*>          = 1:  UNIFORM( 0, 1 )
135*>          = 2:  UNIFORM( -1, 1 )
136*>          = 3:  NORMAL ( 0, 1 )
137*> \endverbatim
138*>
139*> \param[in,out] ISEED
140*> \verbatim
141*>          ISEED is INTEGER array, dimension (4)
142*>          On entry ISEED specifies the seed of the random number
143*>          generator.  The values of ISEED are changed on exit, and can
144*>          be used in the next call to SLATM4 to continue the same
145*>          random number sequence.
146*>          Note: ISEED(4) should be odd, for the random number generator
147*>          used at present.
148*> \endverbatim
149*>
150*> \param[out] A
151*> \verbatim
152*>          A is REAL array, dimension (LDA, N)
153*>          Array to be computed.
154*> \endverbatim
155*>
156*> \param[in] LDA
157*> \verbatim
158*>          LDA is INTEGER
159*>          Leading dimension of A.  Must be at least 1 and at least N.
160*> \endverbatim
161*
162*  Authors:
163*  ========
164*
165*> \author Univ. of Tennessee
166*> \author Univ. of California Berkeley
167*> \author Univ. of Colorado Denver
168*> \author NAG Ltd.
169*
170*> \ingroup single_eig
171*
172*  =====================================================================
173      SUBROUTINE SLATM4( ITYPE, N, NZ1, NZ2, ISIGN, AMAGN, RCOND,
174     $                   TRIANG, IDIST, ISEED, A, LDA )
175*
176*  -- LAPACK test routine --
177*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
178*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
179*
180*     .. Scalar Arguments ..
181      INTEGER            IDIST, ISIGN, ITYPE, LDA, N, NZ1, NZ2
182      REAL               AMAGN, RCOND, TRIANG
183*     ..
184*     .. Array Arguments ..
185      INTEGER            ISEED( 4 )
186      REAL               A( LDA, * )
187*     ..
188*
189*  =====================================================================
190*
191*     .. Parameters ..
192      REAL               ZERO, ONE, TWO
193      PARAMETER          ( ZERO = 0.0E0, ONE = 1.0E0, TWO = 2.0E0 )
194      REAL               HALF
195      PARAMETER          ( HALF = ONE / TWO )
196*     ..
197*     .. Local Scalars ..
198      INTEGER            I, IOFF, ISDB, ISDE, JC, JD, JR, K, KBEG, KEND,
199     $                   KLEN
200      REAL               ALPHA, CL, CR, SAFMIN, SL, SR, SV1, SV2, TEMP
201*     ..
202*     .. External Functions ..
203      REAL               SLAMCH, SLARAN, SLARND
204      EXTERNAL           SLAMCH, SLARAN, SLARND
205*     ..
206*     .. External Subroutines ..
207      EXTERNAL           SLASET
208*     ..
209*     .. Intrinsic Functions ..
210      INTRINSIC          ABS, EXP, LOG, MAX, MIN, MOD, REAL, SQRT
211*     ..
212*     .. Executable Statements ..
213*
214      IF( N.LE.0 )
215     $   RETURN
216      CALL SLASET( 'Full', N, N, ZERO, ZERO, A, LDA )
217*
218*     Insure a correct ISEED
219*
220      IF( MOD( ISEED( 4 ), 2 ).NE.1 )
221     $   ISEED( 4 ) = ISEED( 4 ) + 1
222*
223*     Compute diagonal and subdiagonal according to ITYPE, NZ1, NZ2,
224*     and RCOND
225*
226      IF( ITYPE.NE.0 ) THEN
227         IF( ABS( ITYPE ).GE.4 ) THEN
228            KBEG = MAX( 1, MIN( N, NZ1+1 ) )
229            KEND = MAX( KBEG, MIN( N, N-NZ2 ) )
230            KLEN = KEND + 1 - KBEG
231         ELSE
232            KBEG = 1
233            KEND = N
234            KLEN = N
235         END IF
236         ISDB = 1
237         ISDE = 0
238         GO TO ( 10, 30, 50, 80, 100, 120, 140, 160,
239     $           180, 200 )ABS( ITYPE )
240*
241*        abs(ITYPE) = 1: Identity
242*
243   10    CONTINUE
244         DO 20 JD = 1, N
245            A( JD, JD ) = ONE
246   20    CONTINUE
247         GO TO 220
248*
249*        abs(ITYPE) = 2: Transposed Jordan block
250*
251   30    CONTINUE
252         DO 40 JD = 1, N - 1
253            A( JD+1, JD ) = ONE
254   40    CONTINUE
255         ISDB = 1
256         ISDE = N - 1
257         GO TO 220
258*
259*        abs(ITYPE) = 3: Transposed Jordan block, followed by the
260*                        identity.
261*
262   50    CONTINUE
263         K = ( N-1 ) / 2
264         DO 60 JD = 1, K
265            A( JD+1, JD ) = ONE
266   60    CONTINUE
267         ISDB = 1
268         ISDE = K
269         DO 70 JD = K + 2, 2*K + 1
270            A( JD, JD ) = ONE
271   70    CONTINUE
272         GO TO 220
273*
274*        abs(ITYPE) = 4: 1,...,k
275*
276   80    CONTINUE
277         DO 90 JD = KBEG, KEND
278            A( JD, JD ) = REAL( JD-NZ1 )
279   90    CONTINUE
280         GO TO 220
281*
282*        abs(ITYPE) = 5: One large D value:
283*
284  100    CONTINUE
285         DO 110 JD = KBEG + 1, KEND
286            A( JD, JD ) = RCOND
287  110    CONTINUE
288         A( KBEG, KBEG ) = ONE
289         GO TO 220
290*
291*        abs(ITYPE) = 6: One small D value:
292*
293  120    CONTINUE
294         DO 130 JD = KBEG, KEND - 1
295            A( JD, JD ) = ONE
296  130    CONTINUE
297         A( KEND, KEND ) = RCOND
298         GO TO 220
299*
300*        abs(ITYPE) = 7: Exponentially distributed D values:
301*
302  140    CONTINUE
303         A( KBEG, KBEG ) = ONE
304         IF( KLEN.GT.1 ) THEN
305            ALPHA = RCOND**( ONE / REAL( KLEN-1 ) )
306            DO 150 I = 2, KLEN
307               A( NZ1+I, NZ1+I ) = ALPHA**REAL( I-1 )
308  150       CONTINUE
309         END IF
310         GO TO 220
311*
312*        abs(ITYPE) = 8: Arithmetically distributed D values:
313*
314  160    CONTINUE
315         A( KBEG, KBEG ) = ONE
316         IF( KLEN.GT.1 ) THEN
317            ALPHA = ( ONE-RCOND ) / REAL( KLEN-1 )
318            DO 170 I = 2, KLEN
319               A( NZ1+I, NZ1+I ) = REAL( KLEN-I )*ALPHA + RCOND
320  170       CONTINUE
321         END IF
322         GO TO 220
323*
324*        abs(ITYPE) = 9: Randomly distributed D values on ( RCOND, 1):
325*
326  180    CONTINUE
327         ALPHA = LOG( RCOND )
328         DO 190 JD = KBEG, KEND
329            A( JD, JD ) = EXP( ALPHA*SLARAN( ISEED ) )
330  190    CONTINUE
331         GO TO 220
332*
333*        abs(ITYPE) = 10: Randomly distributed D values from DIST
334*
335  200    CONTINUE
336         DO 210 JD = KBEG, KEND
337            A( JD, JD ) = SLARND( IDIST, ISEED )
338  210    CONTINUE
339*
340  220    CONTINUE
341*
342*        Scale by AMAGN
343*
344         DO 230 JD = KBEG, KEND
345            A( JD, JD ) = AMAGN*REAL( A( JD, JD ) )
346  230    CONTINUE
347         DO 240 JD = ISDB, ISDE
348            A( JD+1, JD ) = AMAGN*REAL( A( JD+1, JD ) )
349  240    CONTINUE
350*
351*        If ISIGN = 1 or 2, assign random signs to diagonal and
352*        subdiagonal
353*
354         IF( ISIGN.GT.0 ) THEN
355            DO 250 JD = KBEG, KEND
356               IF( REAL( A( JD, JD ) ).NE.ZERO ) THEN
357                  IF( SLARAN( ISEED ).GT.HALF )
358     $               A( JD, JD ) = -A( JD, JD )
359               END IF
360  250       CONTINUE
361            DO 260 JD = ISDB, ISDE
362               IF( REAL( A( JD+1, JD ) ).NE.ZERO ) THEN
363                  IF( SLARAN( ISEED ).GT.HALF )
364     $               A( JD+1, JD ) = -A( JD+1, JD )
365               END IF
366  260       CONTINUE
367         END IF
368*
369*        Reverse if ITYPE < 0
370*
371         IF( ITYPE.LT.0 ) THEN
372            DO 270 JD = KBEG, ( KBEG+KEND-1 ) / 2
373               TEMP = A( JD, JD )
374               A( JD, JD ) = A( KBEG+KEND-JD, KBEG+KEND-JD )
375               A( KBEG+KEND-JD, KBEG+KEND-JD ) = TEMP
376  270       CONTINUE
377            DO 280 JD = 1, ( N-1 ) / 2
378               TEMP = A( JD+1, JD )
379               A( JD+1, JD ) = A( N+1-JD, N-JD )
380               A( N+1-JD, N-JD ) = TEMP
381  280       CONTINUE
382         END IF
383*
384*        If ISIGN = 2, and no subdiagonals already, then apply
385*        random rotations to make 2x2 blocks.
386*
387         IF( ISIGN.EQ.2 .AND. ITYPE.NE.2 .AND. ITYPE.NE.3 ) THEN
388            SAFMIN = SLAMCH( 'S' )
389            DO 290 JD = KBEG, KEND - 1, 2
390               IF( SLARAN( ISEED ).GT.HALF ) THEN
391*
392*                 Rotation on left.
393*
394                  CL = TWO*SLARAN( ISEED ) - ONE
395                  SL = TWO*SLARAN( ISEED ) - ONE
396                  TEMP = ONE / MAX( SAFMIN, SQRT( CL**2+SL**2 ) )
397                  CL = CL*TEMP
398                  SL = SL*TEMP
399*
400*                 Rotation on right.
401*
402                  CR = TWO*SLARAN( ISEED ) - ONE
403                  SR = TWO*SLARAN( ISEED ) - ONE
404                  TEMP = ONE / MAX( SAFMIN, SQRT( CR**2+SR**2 ) )
405                  CR = CR*TEMP
406                  SR = SR*TEMP
407*
408*                 Apply
409*
410                  SV1 = A( JD, JD )
411                  SV2 = A( JD+1, JD+1 )
412                  A( JD, JD ) = CL*CR*SV1 + SL*SR*SV2
413                  A( JD+1, JD ) = -SL*CR*SV1 + CL*SR*SV2
414                  A( JD, JD+1 ) = -CL*SR*SV1 + SL*CR*SV2
415                  A( JD+1, JD+1 ) = SL*SR*SV1 + CL*CR*SV2
416               END IF
417  290       CONTINUE
418         END IF
419*
420      END IF
421*
422*     Fill in upper triangle (except for 2x2 blocks)
423*
424      IF( TRIANG.NE.ZERO ) THEN
425         IF( ISIGN.NE.2 .OR. ITYPE.EQ.2 .OR. ITYPE.EQ.3 ) THEN
426            IOFF = 1
427         ELSE
428            IOFF = 2
429            DO 300 JR = 1, N - 1
430               IF( A( JR+1, JR ).EQ.ZERO )
431     $            A( JR, JR+1 ) = TRIANG*SLARND( IDIST, ISEED )
432  300       CONTINUE
433         END IF
434*
435         DO 320 JC = 2, N
436            DO 310 JR = 1, JC - IOFF
437               A( JR, JC ) = TRIANG*SLARND( IDIST, ISEED )
438  310       CONTINUE
439  320    CONTINUE
440      END IF
441*
442      RETURN
443*
444*     End of SLATM4
445*
446      END
447