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