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