LAPACK 3.12.0
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*> \htmlonly
9*> Download ZLANTR + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlantr.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlantr.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlantr.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* DOUBLE PRECISION FUNCTION ZLANTR( NORM, UPLO, DIAG, M, N, A, LDA,
22* WORK )
23*
24* .. Scalar Arguments ..
25* CHARACTER DIAG, NORM, UPLO
26* INTEGER LDA, M, N
27* ..
28* .. Array Arguments ..
29* DOUBLE PRECISION WORK( * )
30* COMPLEX*16 A( LDA, * )
31* ..
32*
33*
34*> \par Purpose:
35* =============
36*>
37*> \verbatim
38*>
39*> ZLANTR returns the value of the one norm, or the Frobenius norm, or
40*> the infinity norm, or the element of largest absolute value of a
41*> trapezoidal or triangular matrix A.
42*> \endverbatim
43*>
44*> \return ZLANTR
45*> \verbatim
46*>
47*> ZLANTR = ( 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 ZLANTR 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 trapezoidal.
75*> = 'U': Upper trapezoidal
76*> = 'L': Lower trapezoidal
77*> Note that A is triangular instead of trapezoidal if M = N.
78*> \endverbatim
79*>
80*> \param[in] DIAG
81*> \verbatim
82*> DIAG is CHARACTER*1
83*> Specifies whether or not the matrix A has unit diagonal.
84*> = 'N': Non-unit diagonal
85*> = 'U': Unit diagonal
86*> \endverbatim
87*>
88*> \param[in] M
89*> \verbatim
90*> M is INTEGER
91*> The number of rows of the matrix A. M >= 0, and if
92*> UPLO = 'U', M <= N. When M = 0, ZLANTR is set to zero.
93*> \endverbatim
94*>
95*> \param[in] N
96*> \verbatim
97*> N is INTEGER
98*> The number of columns of the matrix A. N >= 0, and if
99*> UPLO = 'L', N <= M. When N = 0, ZLANTR is set to zero.
100*> \endverbatim
101*>
102*> \param[in] A
103*> \verbatim
104*> A is COMPLEX*16 array, dimension (LDA,N)
105*> The trapezoidal matrix A (A is triangular if M = N).
106*> If UPLO = 'U', the leading m by n upper trapezoidal part of
107*> the array A contains the upper trapezoidal matrix, and the
108*> strictly lower triangular part of A is not referenced.
109*> If UPLO = 'L', the leading m by n lower trapezoidal part of
110*> the array A contains the lower trapezoidal matrix, and the
111*> strictly upper triangular part of A is not referenced. Note
112*> that when DIAG = 'U', the diagonal elements of A are not
113*> referenced and are assumed to be one.
114*> \endverbatim
115*>
116*> \param[in] LDA
117*> \verbatim
118*> LDA is INTEGER
119*> The leading dimension of the array A. LDA >= max(M,1).
120*> \endverbatim
121*>
122*> \param[out] WORK
123*> \verbatim
124*> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK)),
125*> where LWORK >= M when NORM = 'I'; otherwise, WORK is not
126*> referenced.
127*> \endverbatim
128*
129* Authors:
130* ========
131*
132*> \author Univ. of Tennessee
133*> \author Univ. of California Berkeley
134*> \author Univ. of Colorado Denver
135*> \author NAG Ltd.
136*
137*> \ingroup lantr
138*
139* =====================================================================
140 DOUBLE PRECISION FUNCTION zlantr( NORM, UPLO, DIAG, M, N, A, LDA,
141 $ WORK )
142*
143* -- LAPACK auxiliary routine --
144* -- LAPACK is a software package provided by Univ. of Tennessee, --
145* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146*
147* .. Scalar Arguments ..
148 CHARACTER diag, norm, uplo
149 INTEGER lda, m, n
150* ..
151* .. Array Arguments ..
152 DOUBLE PRECISION work( * )
153 COMPLEX*16 a( lda, * )
154* ..
155*
156* =====================================================================
157*
158* .. Parameters ..
159 DOUBLE PRECISION one, zero
160 parameter( one = 1.0d+0, zero = 0.0d+0 )
161* ..
162* .. Local Scalars ..
163 LOGICAL udiag
164 INTEGER i, j
165 DOUBLE PRECISION scale, sum, value
166* ..
167* .. External Functions ..
168 LOGICAL lsame, disnan
169 EXTERNAL lsame, disnan
170* ..
171* .. External Subroutines ..
172 EXTERNAL zlassq
173* ..
174* .. Intrinsic Functions ..
175 INTRINSIC abs, min, sqrt
176* ..
177* .. Executable Statements ..
178*
179 IF( min( m, n ).EQ.0 ) THEN
180 VALUE = zero
181 ELSE IF( lsame( norm, 'M' ) ) THEN
182*
183* Find max(abs(A(i,j))).
184*
185 IF( lsame( diag, 'U' ) ) THEN
186 VALUE = one
187 IF( lsame( uplo, 'U' ) ) THEN
188 DO 20 j = 1, n
189 DO 10 i = 1, min( m, j-1 )
190 sum = abs( a( i, j ) )
191 IF( VALUE .LT. sum .OR. 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. disnan( sum ) ) VALUE = sum
199 30 CONTINUE
200 40 CONTINUE
201 END IF
202 ELSE
203 VALUE = zero
204 IF( lsame( uplo, 'U' ) ) THEN
205 DO 60 j = 1, n
206 DO 50 i = 1, min( m, j )
207 sum = abs( a( i, j ) )
208 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
209 50 CONTINUE
210 60 CONTINUE
211 ELSE
212 DO 80 j = 1, n
213 DO 70 i = j, m
214 sum = abs( a( i, j ) )
215 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
216 70 CONTINUE
217 80 CONTINUE
218 END IF
219 END IF
220 ELSE IF( ( lsame( norm, 'O' ) ) .OR. ( norm.EQ.'1' ) ) THEN
221*
222* Find norm1(A).
223*
224 VALUE = zero
225 udiag = lsame( diag, 'U' )
226 IF( lsame( uplo, 'U' ) ) THEN
227 DO 110 j = 1, n
228 IF( ( udiag ) .AND. ( j.LE.m ) ) THEN
229 sum = one
230 DO 90 i = 1, j - 1
231 sum = sum + abs( a( i, j ) )
232 90 CONTINUE
233 ELSE
234 sum = zero
235 DO 100 i = 1, min( m, j )
236 sum = sum + abs( a( i, j ) )
237 100 CONTINUE
238 END IF
239 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
240 110 CONTINUE
241 ELSE
242 DO 140 j = 1, n
243 IF( udiag ) THEN
244 sum = one
245 DO 120 i = j + 1, m
246 sum = sum + abs( a( i, j ) )
247 120 CONTINUE
248 ELSE
249 sum = zero
250 DO 130 i = j, m
251 sum = sum + abs( a( i, j ) )
252 130 CONTINUE
253 END IF
254 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
255 140 CONTINUE
256 END IF
257 ELSE IF( lsame( norm, 'I' ) ) THEN
258*
259* Find normI(A).
260*
261 IF( lsame( uplo, 'U' ) ) THEN
262 IF( lsame( diag, 'U' ) ) THEN
263 DO 150 i = 1, m
264 work( i ) = one
265 150 CONTINUE
266 DO 170 j = 1, n
267 DO 160 i = 1, min( m, j-1 )
268 work( i ) = work( i ) + abs( a( i, j ) )
269 160 CONTINUE
270 170 CONTINUE
271 ELSE
272 DO 180 i = 1, m
273 work( i ) = zero
274 180 CONTINUE
275 DO 200 j = 1, n
276 DO 190 i = 1, min( m, j )
277 work( i ) = work( i ) + abs( a( i, j ) )
278 190 CONTINUE
279 200 CONTINUE
280 END IF
281 ELSE
282 IF( lsame( diag, 'U' ) ) THEN
283 DO 210 i = 1, min( m, n )
284 work( i ) = one
285 210 CONTINUE
286 DO 220 i = n + 1, m
287 work( i ) = zero
288 220 CONTINUE
289 DO 240 j = 1, n
290 DO 230 i = j + 1, m
291 work( i ) = work( i ) + abs( a( i, j ) )
292 230 CONTINUE
293 240 CONTINUE
294 ELSE
295 DO 250 i = 1, m
296 work( i ) = zero
297 250 CONTINUE
298 DO 270 j = 1, n
299 DO 260 i = j, m
300 work( i ) = work( i ) + abs( a( i, j ) )
301 260 CONTINUE
302 270 CONTINUE
303 END IF
304 END IF
305 VALUE = zero
306 DO 280 i = 1, m
307 sum = work( i )
308 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
309 280 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 = min( m, n )
318 DO 290 j = 2, n
319 CALL zlassq( min( m, j-1 ), a( 1, j ), 1, scale, sum )
320 290 CONTINUE
321 ELSE
322 scale = zero
323 sum = one
324 DO 300 j = 1, n
325 CALL zlassq( min( m, j ), a( 1, j ), 1, scale, sum )
326 300 CONTINUE
327 END IF
328 ELSE
329 IF( lsame( diag, 'U' ) ) THEN
330 scale = one
331 sum = min( m, n )
332 DO 310 j = 1, n
333 CALL zlassq( m-j, a( min( m, j+1 ), j ), 1, scale,
334 $ sum )
335 310 CONTINUE
336 ELSE
337 scale = zero
338 sum = one
339 DO 320 j = 1, n
340 CALL zlassq( m-j+1, a( j, j ), 1, scale, sum )
341 320 CONTINUE
342 END IF
343 END IF
344 VALUE = scale*sqrt( sum )
345 END IF
346*
347 zlantr = VALUE
348 RETURN
349*
350* End of ZLANTR
351*
352 END
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
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:142
subroutine zlassq(n, x, incx, scale, sumsq)
ZLASSQ updates a sum of squares represented in scaled form.
Definition zlassq.f90:124
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48