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