1 SUBROUTINE ZLAQSP( UPLO, N, AP, S, SCOND, AMAX, EQUED )
2 *
3 * -- LAPACK auxiliary routine (version 3.2) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 CHARACTER EQUED, UPLO
10 INTEGER N
11 DOUBLE PRECISION AMAX, SCOND
12 * ..
13 * .. Array Arguments ..
14 DOUBLE PRECISION S( * )
15 COMPLEX*16 AP( * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * ZLAQSP equilibrates a symmetric matrix A using the scaling factors
22 * in the vector S.
23 *
24 * Arguments
25 * =========
26 *
27 * UPLO (input) CHARACTER*1
28 * Specifies whether the upper or lower triangular part of the
29 * symmetric matrix A is stored.
30 * = 'U': Upper triangular
31 * = 'L': Lower triangular
32 *
33 * N (input) INTEGER
34 * The order of the matrix A. N >= 0.
35 *
36 * AP (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
37 * On entry, the upper or lower triangle of the symmetric matrix
38 * A, packed columnwise in a linear array. The j-th column of A
39 * is stored in the array AP as follows:
40 * if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
41 * if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
42 *
43 * On exit, the equilibrated matrix: diag(S) * A * diag(S), in
44 * the same storage format as A.
45 *
46 * S (input) DOUBLE PRECISION array, dimension (N)
47 * The scale factors for A.
48 *
49 * SCOND (input) DOUBLE PRECISION
50 * Ratio of the smallest S(i) to the largest S(i).
51 *
52 * AMAX (input) DOUBLE PRECISION
53 * Absolute value of largest matrix entry.
54 *
55 * EQUED (output) CHARACTER*1
56 * Specifies whether or not equilibration was done.
57 * = 'N': No equilibration.
58 * = 'Y': Equilibration was done, i.e., A has been replaced by
59 * diag(S) * A * diag(S).
60 *
61 * Internal Parameters
62 * ===================
63 *
64 * THRESH is a threshold value used to decide if scaling should be done
65 * based on the ratio of the scaling factors. If SCOND < THRESH,
66 * scaling is done.
67 *
68 * LARGE and SMALL are threshold values used to decide if scaling should
69 * be done based on the absolute size of the largest matrix element.
70 * If AMAX > LARGE or AMAX < SMALL, scaling is done.
71 *
72 * =====================================================================
73 *
74 * .. Parameters ..
75 DOUBLE PRECISION ONE, THRESH
76 PARAMETER ( ONE = 1.0D+0, THRESH = 0.1D+0 )
77 * ..
78 * .. Local Scalars ..
79 INTEGER I, J, JC
80 DOUBLE PRECISION CJ, LARGE, SMALL
81 * ..
82 * .. External Functions ..
83 LOGICAL LSAME
84 DOUBLE PRECISION DLAMCH
85 EXTERNAL LSAME, DLAMCH
86 * ..
87 * .. Executable Statements ..
88 *
89 * Quick return if possible
90 *
91 IF( N.LE.0 ) THEN
92 EQUED = 'N'
93 RETURN
94 END IF
95 *
96 * Initialize LARGE and SMALL.
97 *
98 SMALL = DLAMCH( 'Safe minimum' ) / DLAMCH( 'Precision' )
99 LARGE = ONE / SMALL
100 *
101 IF( SCOND.GE.THRESH .AND. AMAX.GE.SMALL .AND. AMAX.LE.LARGE ) THEN
102 *
103 * No equilibration
104 *
105 EQUED = 'N'
106 ELSE
107 *
108 * Replace A by diag(S) * A * diag(S).
109 *
110 IF( LSAME( UPLO, 'U' ) ) THEN
111 *
112 * Upper triangle of A is stored.
113 *
114 JC = 1
115 DO 20 J = 1, N
116 CJ = S( J )
117 DO 10 I = 1, J
118 AP( JC+I-1 ) = CJ*S( I )*AP( JC+I-1 )
119 10 CONTINUE
120 JC = JC + J
121 20 CONTINUE
122 ELSE
123 *
124 * Lower triangle of A is stored.
125 *
126 JC = 1
127 DO 40 J = 1, N
128 CJ = S( J )
129 DO 30 I = J, N
130 AP( JC+I-J ) = CJ*S( I )*AP( JC+I-J )
131 30 CONTINUE
132 JC = JC + N - J + 1
133 40 CONTINUE
134 END IF
135 EQUED = 'Y'
136 END IF
137 *
138 RETURN
139 *
140 * End of ZLAQSP
141 *
142 END
2 *
3 * -- LAPACK auxiliary routine (version 3.2) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 CHARACTER EQUED, UPLO
10 INTEGER N
11 DOUBLE PRECISION AMAX, SCOND
12 * ..
13 * .. Array Arguments ..
14 DOUBLE PRECISION S( * )
15 COMPLEX*16 AP( * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * ZLAQSP equilibrates a symmetric matrix A using the scaling factors
22 * in the vector S.
23 *
24 * Arguments
25 * =========
26 *
27 * UPLO (input) CHARACTER*1
28 * Specifies whether the upper or lower triangular part of the
29 * symmetric matrix A is stored.
30 * = 'U': Upper triangular
31 * = 'L': Lower triangular
32 *
33 * N (input) INTEGER
34 * The order of the matrix A. N >= 0.
35 *
36 * AP (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
37 * On entry, the upper or lower triangle of the symmetric matrix
38 * A, packed columnwise in a linear array. The j-th column of A
39 * is stored in the array AP as follows:
40 * if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
41 * if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
42 *
43 * On exit, the equilibrated matrix: diag(S) * A * diag(S), in
44 * the same storage format as A.
45 *
46 * S (input) DOUBLE PRECISION array, dimension (N)
47 * The scale factors for A.
48 *
49 * SCOND (input) DOUBLE PRECISION
50 * Ratio of the smallest S(i) to the largest S(i).
51 *
52 * AMAX (input) DOUBLE PRECISION
53 * Absolute value of largest matrix entry.
54 *
55 * EQUED (output) CHARACTER*1
56 * Specifies whether or not equilibration was done.
57 * = 'N': No equilibration.
58 * = 'Y': Equilibration was done, i.e., A has been replaced by
59 * diag(S) * A * diag(S).
60 *
61 * Internal Parameters
62 * ===================
63 *
64 * THRESH is a threshold value used to decide if scaling should be done
65 * based on the ratio of the scaling factors. If SCOND < THRESH,
66 * scaling is done.
67 *
68 * LARGE and SMALL are threshold values used to decide if scaling should
69 * be done based on the absolute size of the largest matrix element.
70 * If AMAX > LARGE or AMAX < SMALL, scaling is done.
71 *
72 * =====================================================================
73 *
74 * .. Parameters ..
75 DOUBLE PRECISION ONE, THRESH
76 PARAMETER ( ONE = 1.0D+0, THRESH = 0.1D+0 )
77 * ..
78 * .. Local Scalars ..
79 INTEGER I, J, JC
80 DOUBLE PRECISION CJ, LARGE, SMALL
81 * ..
82 * .. External Functions ..
83 LOGICAL LSAME
84 DOUBLE PRECISION DLAMCH
85 EXTERNAL LSAME, DLAMCH
86 * ..
87 * .. Executable Statements ..
88 *
89 * Quick return if possible
90 *
91 IF( N.LE.0 ) THEN
92 EQUED = 'N'
93 RETURN
94 END IF
95 *
96 * Initialize LARGE and SMALL.
97 *
98 SMALL = DLAMCH( 'Safe minimum' ) / DLAMCH( 'Precision' )
99 LARGE = ONE / SMALL
100 *
101 IF( SCOND.GE.THRESH .AND. AMAX.GE.SMALL .AND. AMAX.LE.LARGE ) THEN
102 *
103 * No equilibration
104 *
105 EQUED = 'N'
106 ELSE
107 *
108 * Replace A by diag(S) * A * diag(S).
109 *
110 IF( LSAME( UPLO, 'U' ) ) THEN
111 *
112 * Upper triangle of A is stored.
113 *
114 JC = 1
115 DO 20 J = 1, N
116 CJ = S( J )
117 DO 10 I = 1, J
118 AP( JC+I-1 ) = CJ*S( I )*AP( JC+I-1 )
119 10 CONTINUE
120 JC = JC + J
121 20 CONTINUE
122 ELSE
123 *
124 * Lower triangle of A is stored.
125 *
126 JC = 1
127 DO 40 J = 1, N
128 CJ = S( J )
129 DO 30 I = J, N
130 AP( JC+I-J ) = CJ*S( I )*AP( JC+I-J )
131 30 CONTINUE
132 JC = JC + N - J + 1
133 40 CONTINUE
134 END IF
135 EQUED = 'Y'
136 END IF
137 *
138 RETURN
139 *
140 * End of ZLAQSP
141 *
142 END