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