OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
zlantb.f
Go to the documentation of this file.
1*> \brief \b ZLANTB returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a triangular band matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZLANTB + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlantb.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlantb.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlantb.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* DOUBLE PRECISION FUNCTION ZLANTB( NORM, UPLO, DIAG, N, K, AB,
22* LDAB, WORK )
23*
24* .. Scalar Arguments ..
25* CHARACTER DIAG, NORM, UPLO
26* INTEGER K, LDAB, N
27* ..
28* .. Array Arguments ..
29* DOUBLE PRECISION WORK( * )
30* COMPLEX*16 AB( LDAB, * )
31* ..
32*
33*
34*> \par Purpose:
35* =============
36*>
37*> \verbatim
38*>
39*> ZLANTB returns the value of the one norm, or the Frobenius norm, or
40*> the infinity norm, or the element of largest absolute value of an
41*> n by n triangular band matrix A, with ( k + 1 ) diagonals.
42*> \endverbatim
43*>
44*> \return ZLANTB
45*> \verbatim
46*>
47*> ZLANTB = ( max(abs(A(i,j))), NORM = 'M' or 'm'
48*> (
49*> ( norm1(A), NORM = '1', 'O' or 'o'
50*> (
51*> ( normI(A), NORM = 'I' or 'i'
52*> (
53*> ( normF(A), NORM = 'F', 'f', 'E' or 'e'
54*>
55*> where norm1 denotes the one norm of a matrix (maximum column sum),
56*> normI denotes the infinity norm of a matrix (maximum row sum) and
57*> normF denotes the Frobenius norm of a matrix (square root of sum of
58*> squares). Note that max(abs(A(i,j))) is not a consistent matrix norm.
59*> \endverbatim
60*
61* Arguments:
62* ==========
63*
64*> \param[in] NORM
65*> \verbatim
66*> NORM is CHARACTER*1
67*> Specifies the value to be returned in ZLANTB as described
68*> above.
69*> \endverbatim
70*>
71*> \param[in] UPLO
72*> \verbatim
73*> UPLO is CHARACTER*1
74*> Specifies whether the matrix A is upper or lower triangular.
75*> = 'U': Upper triangular
76*> = 'L': Lower triangular
77*> \endverbatim
78*>
79*> \param[in] DIAG
80*> \verbatim
81*> DIAG is CHARACTER*1
82*> Specifies whether or not the matrix A is unit triangular.
83*> = 'N': Non-unit triangular
84*> = 'U': Unit triangular
85*> \endverbatim
86*>
87*> \param[in] N
88*> \verbatim
89*> N is INTEGER
90*> The order of the matrix A. N >= 0. When N = 0, ZLANTB is
91*> set to zero.
92*> \endverbatim
93*>
94*> \param[in] K
95*> \verbatim
96*> K is INTEGER
97*> The number of super-diagonals of the matrix A if UPLO = 'U',
98*> or the number of sub-diagonals of the matrix A if UPLO = 'L'.
99*> K >= 0.
100*> \endverbatim
101*>
102*> \param[in] AB
103*> \verbatim
104*> AB is COMPLEX*16 array, dimension (LDAB,N)
105*> The upper or lower triangular band matrix A, stored in the
106*> first k+1 rows of AB. The j-th column of A is stored
107*> in the j-th column of the array AB as follows:
108*> if UPLO = 'U', AB(k+1+i-j,j) = A(i,j) for max(1,j-k)<=i<=j;
109*> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+k).
110*> Note that when DIAG = 'U', the elements of the array AB
111*> corresponding to the diagonal elements of the matrix A are
112*> not referenced, but are assumed to be one.
113*> \endverbatim
114*>
115*> \param[in] LDAB
116*> \verbatim
117*> LDAB is INTEGER
118*> The leading dimension of the array AB. LDAB >= K+1.
119*> \endverbatim
120*>
121*> \param[out] WORK
122*> \verbatim
123*> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK)),
124*> where LWORK >= N when NORM = 'I'; otherwise, WORK is not
125*> referenced.
126*> \endverbatim
127*
128* Authors:
129* ========
130*
131*> \author Univ. of Tennessee
132*> \author Univ. of California Berkeley
133*> \author Univ. of Colorado Denver
134*> \author NAG Ltd.
135*
136*> \ingroup complex16OTHERauxiliary
137*
138* =====================================================================
139 DOUBLE PRECISION FUNCTION zlantb( NORM, UPLO, DIAG, N, K, AB,
140 $ LDAB, WORK )
141*
142* -- LAPACK auxiliary routine --
143* -- LAPACK is a software package provided by Univ. of Tennessee, --
144* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
145*
146* .. Scalar Arguments ..
147 CHARACTER diag, norm, uplo
148 INTEGER k, ldab, n
149* ..
150* .. Array Arguments ..
151 DOUBLE PRECISION work( * )
152 COMPLEX*16 ab( ldab, * )
153* ..
154*
155* =====================================================================
156*
157* .. Parameters ..
158 DOUBLE PRECISION one, zero
159 parameter( one = 1.0d+0, zero = 0.0d+0 )
160* ..
161* .. Local Scalars ..
162 LOGICAL udiag
163 INTEGER i, j, l
164 DOUBLE PRECISION scale, sum, value
165* ..
166* .. External Functions ..
167 LOGICAL lsame, disnan
168 EXTERNAL lsame, disnan
169* ..
170* .. External Subroutines ..
171 EXTERNAL zlassq
172* ..
173* .. Intrinsic Functions ..
174 INTRINSIC abs, max, min, sqrt
175* ..
176* .. Executable Statements ..
177*
178 IF( n.EQ.0 ) THEN
179 VALUE = zero
180 ELSE IF( lsame( norm, 'm' ) ) THEN
181*
182* Find max(abs(A(i,j))).
183*
184 IF( LSAME( DIAG, 'u' ) ) THEN
185 VALUE = ONE
186 IF( LSAME( UPLO, 'u' ) ) THEN
187 DO 20 J = 1, N
188 DO 10 I = MAX( K+2-J, 1 ), K
189 SUM = ABS( AB( I, J ) )
190.LT..OR. IF( VALUE SUM DISNAN( SUM ) ) VALUE = SUM
191 10 CONTINUE
192 20 CONTINUE
193 ELSE
194 DO 40 J = 1, N
195 DO 30 I = 2, MIN( N+1-J, K+1 )
196 SUM = ABS( AB( I, J ) )
197.LT..OR. IF( VALUE SUM DISNAN( SUM ) ) VALUE = SUM
198 30 CONTINUE
199 40 CONTINUE
200 END IF
201 ELSE
202 VALUE = ZERO
203 IF( LSAME( UPLO, 'u' ) ) THEN
204 DO 60 J = 1, N
205 DO 50 I = MAX( K+2-J, 1 ), K + 1
206 SUM = ABS( AB( I, J ) )
207.LT..OR. IF( VALUE SUM DISNAN( SUM ) ) VALUE = SUM
208 50 CONTINUE
209 60 CONTINUE
210 ELSE
211 DO 80 J = 1, N
212 DO 70 I = 1, MIN( N+1-J, K+1 )
213 SUM = ABS( AB( I, J ) )
214.LT..OR. IF( VALUE SUM DISNAN( SUM ) ) VALUE = SUM
215 70 CONTINUE
216 80 CONTINUE
217 END IF
218 END IF
219 ELSE IF( ( LSAME( NORM, 'o.OR..EQ.' ) ) ( NORM'1' ) ) THEN
220*
221* Find norm1(A).
222*
223 VALUE = ZERO
224 UDIAG = LSAME( DIAG, 'u' )
225 IF( LSAME( UPLO, 'u' ) ) THEN
226 DO 110 J = 1, N
227 IF( UDIAG ) THEN
228 SUM = ONE
229 DO 90 I = MAX( K+2-J, 1 ), K
230 SUM = SUM + ABS( AB( I, J ) )
231 90 CONTINUE
232 ELSE
233 SUM = ZERO
234 DO 100 I = MAX( K+2-J, 1 ), K + 1
235 SUM = SUM + ABS( AB( I, J ) )
236 100 CONTINUE
237 END IF
238.LT..OR. IF( VALUE SUM DISNAN( SUM ) ) VALUE = SUM
239 110 CONTINUE
240 ELSE
241 DO 140 J = 1, N
242 IF( UDIAG ) THEN
243 SUM = ONE
244 DO 120 I = 2, MIN( N+1-J, K+1 )
245 SUM = SUM + ABS( AB( I, J ) )
246 120 CONTINUE
247 ELSE
248 SUM = ZERO
249 DO 130 I = 1, MIN( N+1-J, K+1 )
250 SUM = SUM + ABS( AB( I, J ) )
251 130 CONTINUE
252 END IF
253.LT..OR. IF( VALUE SUM DISNAN( SUM ) ) VALUE = SUM
254 140 CONTINUE
255 END IF
256 ELSE IF( LSAME( NORM, 'i' ) ) THEN
257*
258* Find normI(A).
259*
260 VALUE = ZERO
261 IF( LSAME( UPLO, 'u' ) ) THEN
262 IF( LSAME( DIAG, 'u' ) ) THEN
263 DO 150 I = 1, N
264 WORK( I ) = ONE
265 150 CONTINUE
266 DO 170 J = 1, N
267 L = K + 1 - J
268 DO 160 I = MAX( 1, J-K ), J - 1
269 WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
270 160 CONTINUE
271 170 CONTINUE
272 ELSE
273 DO 180 I = 1, N
274 WORK( I ) = ZERO
275 180 CONTINUE
276 DO 200 J = 1, N
277 L = K + 1 - J
278 DO 190 I = MAX( 1, J-K ), J
279 WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
280 190 CONTINUE
281 200 CONTINUE
282 END IF
283 ELSE
284 IF( LSAME( DIAG, 'u' ) ) THEN
285 DO 210 I = 1, N
286 WORK( I ) = ONE
287 210 CONTINUE
288 DO 230 J = 1, N
289 L = 1 - J
290 DO 220 I = J + 1, MIN( N, J+K )
291 WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
292 220 CONTINUE
293 230 CONTINUE
294 ELSE
295 DO 240 I = 1, N
296 WORK( I ) = ZERO
297 240 CONTINUE
298 DO 260 J = 1, N
299 L = 1 - J
300 DO 250 I = J, MIN( N, J+K )
301 WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
302 250 CONTINUE
303 260 CONTINUE
304 END IF
305 END IF
306 DO 270 I = 1, N
307 SUM = WORK( I )
308.LT..OR. IF( VALUE SUM DISNAN( SUM ) ) VALUE = SUM
309 270 CONTINUE
310 ELSE IF( ( LSAME( NORM, 'f.OR.' ) ) ( LSAME( NORM, 'e' ) ) ) THEN
311*
312* Find normF(A).
313*
314 IF( LSAME( UPLO, 'u' ) ) THEN
315 IF( LSAME( DIAG, 'u' ) ) THEN
316 SCALE = ONE
317 SUM = N
318.GT. IF( K0 ) THEN
319 DO 280 J = 2, N
320 CALL ZLASSQ( MIN( J-1, K ),
321 $ AB( MAX( K+2-J, 1 ), J ), 1, SCALE,
322 $ SUM )
323 280 CONTINUE
324 END IF
325 ELSE
326 SCALE = ZERO
327 SUM = ONE
328 DO 290 J = 1, N
329 CALL ZLASSQ( MIN( J, K+1 ), AB( MAX( K+2-J, 1 ), J ),
330 $ 1, SCALE, SUM )
331 290 CONTINUE
332 END IF
333 ELSE
334 IF( LSAME( DIAG, 'u' ) ) THEN
335 SCALE = ONE
336 SUM = N
337.GT. IF( K0 ) THEN
338 DO 300 J = 1, N - 1
339 CALL ZLASSQ( MIN( N-J, K ), AB( 2, J ), 1, SCALE,
340 $ SUM )
341 300 CONTINUE
342 END IF
343 ELSE
344 SCALE = ZERO
345 SUM = ONE
346 DO 310 J = 1, N
347 CALL ZLASSQ( MIN( N-J+1, K+1 ), AB( 1, J ), 1, SCALE,
348 $ SUM )
349 310 CONTINUE
350 END IF
351 END IF
352 VALUE = SCALE*SQRT( SUM )
353 END IF
354*
355 ZLANTB = VALUE
356 RETURN
357*
358* End of ZLANTB
359*
360 END
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
subroutine zlassq(n, x, incx, scl, sumsq)
ZLASSQ updates a sum of squares represented in scaled form.
Definition zlassq.f90:137
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
logical function lsame(ca, cb)
LSAME
Definition lsame.f:53
double precision function zlantb(norm, uplo, diag, n, k, ab, ldab, work)
ZLANTB returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition zlantb.f:141
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21