PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
cqrt13.f
Go to the documentation of this file.
1  SUBROUTINE cqrt13( SCALE, M, N, A, LDA, NORMA, ISEED )
2 *
3 * -- LAPACK test routine (version 3.1) --
4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5 * November 2006
6 *
7 * .. Scalar Arguments ..
8  INTEGER lda, m, n, scale
9  REAL norma
10 * ..
11 * .. Array Arguments ..
12  INTEGER iseed( 4 )
13  COMPLEX a( lda, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * CQRT13 generates a full-rank matrix that may be scaled to have large
20 * or small norm.
21 *
22 * Arguments
23 * =========
24 *
25 * SCALE (input) INTEGER
26 * SCALE = 1: normally scaled matrix
27 * SCALE = 2: matrix scaled up
28 * SCALE = 3: matrix scaled down
29 *
30 * M (input) INTEGER
31 * The number of rows of the matrix A.
32 *
33 * N (input) INTEGER
34 * The number of columns of A.
35 *
36 * A (output) COMPLEX array, dimension (LDA,N)
37 * The M-by-N matrix A.
38 *
39 * LDA (input) INTEGER
40 * The leading dimension of the array A.
41 *
42 * NORMA (output) REAL
43 * The one-norm of A.
44 *
45 * ISEED (input/output) integer array, dimension (4)
46 * Seed for random number generator
47 *
48 * =====================================================================
49 *
50 * .. Parameters ..
51  REAL one
52  parameter( one = 1.0e0 )
53 * ..
54 * .. Local Scalars ..
55  INTEGER info, j
56  REAL bignum, smlnum
57 * ..
58 * .. External Functions ..
59  REAL clange, scasum, slamch
60  EXTERNAL clange, scasum, slamch
61 * ..
62 * .. External Subroutines ..
63  EXTERNAL clarnv, clascl, slabad
64 * ..
65 * .. Intrinsic Functions ..
66  INTRINSIC cmplx, REAL, sign
67 * ..
68 * .. Local Arrays ..
69  REAL dummy( 1 )
70 * ..
71 * .. Executable Statements ..
72 *
73  IF( m.LE.0 .OR. n.LE.0 )
74  $ return
75 *
76 * benign matrix
77 *
78  DO 10 j = 1, n
79  CALL clarnv( 2, iseed, m, a( 1, j ) )
80  IF( j.LE.m ) THEN
81  a( j, j ) = a( j, j ) + cmplx( sign( scasum( m, a( 1, j ),
82  $ 1 ), REAL( A( J, J ) ) ) )
83  END IF
84  10 continue
85 *
86 * scaled versions
87 *
88  IF( scale.NE.1 ) THEN
89  norma = clange( 'Max', m, n, a, lda, dummy )
90  smlnum = slamch( 'Safe minimum' )
91  bignum = one / smlnum
92  CALL slabad( smlnum, bignum )
93  smlnum = smlnum / slamch( 'Epsilon' )
94  bignum = one / smlnum
95 *
96  IF( scale.EQ.2 ) THEN
97 *
98 * matrix scaled up
99 *
100  CALL clascl( 'General', 0, 0, norma, bignum, m, n, a, lda,
101  $ info )
102  ELSE IF( scale.EQ.3 ) THEN
103 *
104 * matrix scaled down
105 *
106  CALL clascl( 'General', 0, 0, norma, smlnum, m, n, a, lda,
107  $ info )
108  END IF
109  END IF
110 *
111  norma = clange( 'One-norm', m, n, a, lda, dummy )
112  return
113 *
114 * End of CQRT13
115 *
116  END