1 DOUBLE PRECISION FUNCTION ZLANSB( NORM, UPLO, N, K, AB, LDAB,
2 $ WORK )
3 *
4 * -- LAPACK auxiliary routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10 CHARACTER NORM, UPLO
11 INTEGER K, LDAB, N
12 * ..
13 * .. Array Arguments ..
14 DOUBLE PRECISION WORK( * )
15 COMPLEX*16 AB( LDAB, * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * ZLANSB returns the value of the one norm, or the Frobenius norm, or
22 * the infinity norm, or the element of largest absolute value of an
23 * n by n symmetric band matrix A, with k super-diagonals.
24 *
25 * Description
26 * ===========
27 *
28 * ZLANSB returns the value
29 *
30 * ZLANSB = ( max(abs(A(i,j))), NORM = 'M' or 'm'
31 * (
32 * ( norm1(A), NORM = '1', 'O' or 'o'
33 * (
34 * ( normI(A), NORM = 'I' or 'i'
35 * (
36 * ( normF(A), NORM = 'F', 'f', 'E' or 'e'
37 *
38 * where norm1 denotes the one norm of a matrix (maximum column sum),
39 * normI denotes the infinity norm of a matrix (maximum row sum) and
40 * normF denotes the Frobenius norm of a matrix (square root of sum of
41 * squares). Note that max(abs(A(i,j))) is not a consistent matrix norm.
42 *
43 * Arguments
44 * =========
45 *
46 * NORM (input) CHARACTER*1
47 * Specifies the value to be returned in ZLANSB as described
48 * above.
49 *
50 * UPLO (input) CHARACTER*1
51 * Specifies whether the upper or lower triangular part of the
52 * band matrix A is supplied.
53 * = 'U': Upper triangular part is supplied
54 * = 'L': Lower triangular part is supplied
55 *
56 * N (input) INTEGER
57 * The order of the matrix A. N >= 0. When N = 0, ZLANSB is
58 * set to zero.
59 *
60 * K (input) INTEGER
61 * The number of super-diagonals or sub-diagonals of the
62 * band matrix A. K >= 0.
63 *
64 * AB (input) COMPLEX*16 array, dimension (LDAB,N)
65 * The upper or lower triangle of the symmetric band matrix A,
66 * stored in the first K+1 rows of AB. The j-th column of A is
67 * stored in the j-th column of the array AB as follows:
68 * if UPLO = 'U', AB(k+1+i-j,j) = A(i,j) for max(1,j-k)<=i<=j;
69 * if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+k).
70 *
71 * LDAB (input) INTEGER
72 * The leading dimension of the array AB. LDAB >= K+1.
73 *
74 * WORK (workspace) DOUBLE PRECISION array, dimension (MAX(1,LWORK)),
75 * where LWORK >= N when NORM = 'I' or '1' or 'O'; otherwise,
76 * WORK is not referenced.
77 *
78 * =====================================================================
79 *
80 * .. Parameters ..
81 DOUBLE PRECISION ONE, ZERO
82 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
83 * ..
84 * .. Local Scalars ..
85 INTEGER I, J, L
86 DOUBLE PRECISION ABSA, SCALE, SUM, VALUE
87 * ..
88 * .. External Functions ..
89 LOGICAL LSAME
90 EXTERNAL LSAME
91 * ..
92 * .. External Subroutines ..
93 EXTERNAL ZLASSQ
94 * ..
95 * .. Intrinsic Functions ..
96 INTRINSIC ABS, MAX, MIN, SQRT
97 * ..
98 * .. Executable Statements ..
99 *
100 IF( N.EQ.0 ) THEN
101 VALUE = ZERO
102 ELSE IF( LSAME( NORM, 'M' ) ) THEN
103 *
104 * Find max(abs(A(i,j))).
105 *
106 VALUE = ZERO
107 IF( LSAME( UPLO, 'U' ) ) THEN
108 DO 20 J = 1, N
109 DO 10 I = MAX( K+2-J, 1 ), K + 1
110 VALUE = MAX( VALUE, ABS( AB( I, J ) ) )
111 10 CONTINUE
112 20 CONTINUE
113 ELSE
114 DO 40 J = 1, N
115 DO 30 I = 1, MIN( N+1-J, K+1 )
116 VALUE = MAX( VALUE, ABS( AB( I, J ) ) )
117 30 CONTINUE
118 40 CONTINUE
119 END IF
120 ELSE IF( ( LSAME( NORM, 'I' ) ) .OR. ( LSAME( NORM, 'O' ) ) .OR.
121 $ ( NORM.EQ.'1' ) ) THEN
122 *
123 * Find normI(A) ( = norm1(A), since A is symmetric).
124 *
125 VALUE = ZERO
126 IF( LSAME( UPLO, 'U' ) ) THEN
127 DO 60 J = 1, N
128 SUM = ZERO
129 L = K + 1 - J
130 DO 50 I = MAX( 1, J-K ), J - 1
131 ABSA = ABS( AB( L+I, J ) )
132 SUM = SUM + ABSA
133 WORK( I ) = WORK( I ) + ABSA
134 50 CONTINUE
135 WORK( J ) = SUM + ABS( AB( K+1, J ) )
136 60 CONTINUE
137 DO 70 I = 1, N
138 VALUE = MAX( VALUE, WORK( I ) )
139 70 CONTINUE
140 ELSE
141 DO 80 I = 1, N
142 WORK( I ) = ZERO
143 80 CONTINUE
144 DO 100 J = 1, N
145 SUM = WORK( J ) + ABS( AB( 1, J ) )
146 L = 1 - J
147 DO 90 I = J + 1, MIN( N, J+K )
148 ABSA = ABS( AB( L+I, J ) )
149 SUM = SUM + ABSA
150 WORK( I ) = WORK( I ) + ABSA
151 90 CONTINUE
152 VALUE = MAX( VALUE, SUM )
153 100 CONTINUE
154 END IF
155 ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
156 *
157 * Find normF(A).
158 *
159 SCALE = ZERO
160 SUM = ONE
161 IF( K.GT.0 ) THEN
162 IF( LSAME( UPLO, 'U' ) ) THEN
163 DO 110 J = 2, N
164 CALL ZLASSQ( MIN( J-1, K ), AB( MAX( K+2-J, 1 ), J ),
165 $ 1, SCALE, SUM )
166 110 CONTINUE
167 L = K + 1
168 ELSE
169 DO 120 J = 1, N - 1
170 CALL ZLASSQ( MIN( N-J, K ), AB( 2, J ), 1, SCALE,
171 $ SUM )
172 120 CONTINUE
173 L = 1
174 END IF
175 SUM = 2*SUM
176 ELSE
177 L = 1
178 END IF
179 CALL ZLASSQ( N, AB( L, 1 ), LDAB, SCALE, SUM )
180 VALUE = SCALE*SQRT( SUM )
181 END IF
182 *
183 ZLANSB = VALUE
184 RETURN
185 *
186 * End of ZLANSB
187 *
188 END
2 $ WORK )
3 *
4 * -- LAPACK auxiliary routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10 CHARACTER NORM, UPLO
11 INTEGER K, LDAB, N
12 * ..
13 * .. Array Arguments ..
14 DOUBLE PRECISION WORK( * )
15 COMPLEX*16 AB( LDAB, * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * ZLANSB returns the value of the one norm, or the Frobenius norm, or
22 * the infinity norm, or the element of largest absolute value of an
23 * n by n symmetric band matrix A, with k super-diagonals.
24 *
25 * Description
26 * ===========
27 *
28 * ZLANSB returns the value
29 *
30 * ZLANSB = ( max(abs(A(i,j))), NORM = 'M' or 'm'
31 * (
32 * ( norm1(A), NORM = '1', 'O' or 'o'
33 * (
34 * ( normI(A), NORM = 'I' or 'i'
35 * (
36 * ( normF(A), NORM = 'F', 'f', 'E' or 'e'
37 *
38 * where norm1 denotes the one norm of a matrix (maximum column sum),
39 * normI denotes the infinity norm of a matrix (maximum row sum) and
40 * normF denotes the Frobenius norm of a matrix (square root of sum of
41 * squares). Note that max(abs(A(i,j))) is not a consistent matrix norm.
42 *
43 * Arguments
44 * =========
45 *
46 * NORM (input) CHARACTER*1
47 * Specifies the value to be returned in ZLANSB as described
48 * above.
49 *
50 * UPLO (input) CHARACTER*1
51 * Specifies whether the upper or lower triangular part of the
52 * band matrix A is supplied.
53 * = 'U': Upper triangular part is supplied
54 * = 'L': Lower triangular part is supplied
55 *
56 * N (input) INTEGER
57 * The order of the matrix A. N >= 0. When N = 0, ZLANSB is
58 * set to zero.
59 *
60 * K (input) INTEGER
61 * The number of super-diagonals or sub-diagonals of the
62 * band matrix A. K >= 0.
63 *
64 * AB (input) COMPLEX*16 array, dimension (LDAB,N)
65 * The upper or lower triangle of the symmetric band matrix A,
66 * stored in the first K+1 rows of AB. The j-th column of A is
67 * stored in the j-th column of the array AB as follows:
68 * if UPLO = 'U', AB(k+1+i-j,j) = A(i,j) for max(1,j-k)<=i<=j;
69 * if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+k).
70 *
71 * LDAB (input) INTEGER
72 * The leading dimension of the array AB. LDAB >= K+1.
73 *
74 * WORK (workspace) DOUBLE PRECISION array, dimension (MAX(1,LWORK)),
75 * where LWORK >= N when NORM = 'I' or '1' or 'O'; otherwise,
76 * WORK is not referenced.
77 *
78 * =====================================================================
79 *
80 * .. Parameters ..
81 DOUBLE PRECISION ONE, ZERO
82 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
83 * ..
84 * .. Local Scalars ..
85 INTEGER I, J, L
86 DOUBLE PRECISION ABSA, SCALE, SUM, VALUE
87 * ..
88 * .. External Functions ..
89 LOGICAL LSAME
90 EXTERNAL LSAME
91 * ..
92 * .. External Subroutines ..
93 EXTERNAL ZLASSQ
94 * ..
95 * .. Intrinsic Functions ..
96 INTRINSIC ABS, MAX, MIN, SQRT
97 * ..
98 * .. Executable Statements ..
99 *
100 IF( N.EQ.0 ) THEN
101 VALUE = ZERO
102 ELSE IF( LSAME( NORM, 'M' ) ) THEN
103 *
104 * Find max(abs(A(i,j))).
105 *
106 VALUE = ZERO
107 IF( LSAME( UPLO, 'U' ) ) THEN
108 DO 20 J = 1, N
109 DO 10 I = MAX( K+2-J, 1 ), K + 1
110 VALUE = MAX( VALUE, ABS( AB( I, J ) ) )
111 10 CONTINUE
112 20 CONTINUE
113 ELSE
114 DO 40 J = 1, N
115 DO 30 I = 1, MIN( N+1-J, K+1 )
116 VALUE = MAX( VALUE, ABS( AB( I, J ) ) )
117 30 CONTINUE
118 40 CONTINUE
119 END IF
120 ELSE IF( ( LSAME( NORM, 'I' ) ) .OR. ( LSAME( NORM, 'O' ) ) .OR.
121 $ ( NORM.EQ.'1' ) ) THEN
122 *
123 * Find normI(A) ( = norm1(A), since A is symmetric).
124 *
125 VALUE = ZERO
126 IF( LSAME( UPLO, 'U' ) ) THEN
127 DO 60 J = 1, N
128 SUM = ZERO
129 L = K + 1 - J
130 DO 50 I = MAX( 1, J-K ), J - 1
131 ABSA = ABS( AB( L+I, J ) )
132 SUM = SUM + ABSA
133 WORK( I ) = WORK( I ) + ABSA
134 50 CONTINUE
135 WORK( J ) = SUM + ABS( AB( K+1, J ) )
136 60 CONTINUE
137 DO 70 I = 1, N
138 VALUE = MAX( VALUE, WORK( I ) )
139 70 CONTINUE
140 ELSE
141 DO 80 I = 1, N
142 WORK( I ) = ZERO
143 80 CONTINUE
144 DO 100 J = 1, N
145 SUM = WORK( J ) + ABS( AB( 1, J ) )
146 L = 1 - J
147 DO 90 I = J + 1, MIN( N, J+K )
148 ABSA = ABS( AB( L+I, J ) )
149 SUM = SUM + ABSA
150 WORK( I ) = WORK( I ) + ABSA
151 90 CONTINUE
152 VALUE = MAX( VALUE, SUM )
153 100 CONTINUE
154 END IF
155 ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
156 *
157 * Find normF(A).
158 *
159 SCALE = ZERO
160 SUM = ONE
161 IF( K.GT.0 ) THEN
162 IF( LSAME( UPLO, 'U' ) ) THEN
163 DO 110 J = 2, N
164 CALL ZLASSQ( MIN( J-1, K ), AB( MAX( K+2-J, 1 ), J ),
165 $ 1, SCALE, SUM )
166 110 CONTINUE
167 L = K + 1
168 ELSE
169 DO 120 J = 1, N - 1
170 CALL ZLASSQ( MIN( N-J, K ), AB( 2, J ), 1, SCALE,
171 $ SUM )
172 120 CONTINUE
173 L = 1
174 END IF
175 SUM = 2*SUM
176 ELSE
177 L = 1
178 END IF
179 CALL ZLASSQ( N, AB( L, 1 ), LDAB, SCALE, SUM )
180 VALUE = SCALE*SQRT( SUM )
181 END IF
182 *
183 ZLANSB = VALUE
184 RETURN
185 *
186 * End of ZLANSB
187 *
188 END