LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
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 *> \date December 2016
138 *
139 *> \ingroup complex16OTHERauxiliary
140 *
141 * =====================================================================
142  DOUBLE PRECISION FUNCTION zlantr( NORM, UPLO, DIAG, M, N, A, LDA,
143  $ WORK )
144 *
145 * -- LAPACK auxiliary routine (version 3.7.0) --
146 * -- LAPACK is a software package provided by Univ. of Tennessee, --
147 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148 * December 2016
149 *
150  IMPLICIT NONE
151 * .. Scalar Arguments ..
152  CHARACTER diag, norm, uplo
153  INTEGER lda, m, n
154 * ..
155 * .. Array Arguments ..
156  DOUBLE PRECISION work( * )
157  COMPLEX*16 a( lda, * )
158 * ..
159 *
160 * =====================================================================
161 *
162 * .. Parameters ..
163  DOUBLE PRECISION one, zero
164  parameter( one = 1.0d+0, zero = 0.0d+0 )
165 * ..
166 * .. Local Scalars ..
167  LOGICAL udiag
168  INTEGER i, j
169  DOUBLE PRECISION sum, value
170 * ..
171 * .. Local Arrays ..
172  DOUBLE PRECISION ssq( 2 ), colssq( 2 )
173 * ..
174 * .. External Functions ..
175  LOGICAL lsame, disnan
176  EXTERNAL lsame, disnan
177 * ..
178 * .. External Subroutines ..
179  EXTERNAL zlassq, dcombssq
180 * ..
181 * .. Intrinsic Functions ..
182  INTRINSIC abs, min, sqrt
183 * ..
184 * .. Executable Statements ..
185 *
186  IF( min( m, n ).EQ.0 ) THEN
187  VALUE = zero
188  ELSE IF( lsame( norm, 'M' ) ) THEN
189 *
190 * Find max(abs(A(i,j))).
191 *
192  IF( lsame( diag, 'U' ) ) THEN
193  VALUE = one
194  IF( lsame( uplo, 'U' ) ) THEN
195  DO 20 j = 1, n
196  DO 10 i = 1, min( m, j-1 )
197  sum = abs( a( i, j ) )
198  IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
199  10 CONTINUE
200  20 CONTINUE
201  ELSE
202  DO 40 j = 1, n
203  DO 30 i = j + 1, m
204  sum = abs( a( i, j ) )
205  IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
206  30 CONTINUE
207  40 CONTINUE
208  END IF
209  ELSE
210  VALUE = zero
211  IF( lsame( uplo, 'U' ) ) THEN
212  DO 60 j = 1, n
213  DO 50 i = 1, min( m, j )
214  sum = abs( a( i, j ) )
215  IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
216  50 CONTINUE
217  60 CONTINUE
218  ELSE
219  DO 80 j = 1, n
220  DO 70 i = j, m
221  sum = abs( a( i, j ) )
222  IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
223  70 CONTINUE
224  80 CONTINUE
225  END IF
226  END IF
227  ELSE IF( ( lsame( norm, 'O' ) ) .OR. ( norm.EQ.'1' ) ) THEN
228 *
229 * Find norm1(A).
230 *
231  VALUE = zero
232  udiag = lsame( diag, 'U' )
233  IF( lsame( uplo, 'U' ) ) THEN
234  DO 110 j = 1, n
235  IF( ( udiag ) .AND. ( j.LE.m ) ) THEN
236  sum = one
237  DO 90 i = 1, j - 1
238  sum = sum + abs( a( i, j ) )
239  90 CONTINUE
240  ELSE
241  sum = zero
242  DO 100 i = 1, min( m, j )
243  sum = sum + abs( a( i, j ) )
244  100 CONTINUE
245  END IF
246  IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
247  110 CONTINUE
248  ELSE
249  DO 140 j = 1, n
250  IF( udiag ) THEN
251  sum = one
252  DO 120 i = j + 1, m
253  sum = sum + abs( a( i, j ) )
254  120 CONTINUE
255  ELSE
256  sum = zero
257  DO 130 i = j, m
258  sum = sum + abs( a( i, j ) )
259  130 CONTINUE
260  END IF
261  IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
262  140 CONTINUE
263  END IF
264  ELSE IF( lsame( norm, 'I' ) ) THEN
265 *
266 * Find normI(A).
267 *
268  IF( lsame( uplo, 'U' ) ) THEN
269  IF( lsame( diag, 'U' ) ) THEN
270  DO 150 i = 1, m
271  work( i ) = one
272  150 CONTINUE
273  DO 170 j = 1, n
274  DO 160 i = 1, min( m, j-1 )
275  work( i ) = work( i ) + abs( a( i, j ) )
276  160 CONTINUE
277  170 CONTINUE
278  ELSE
279  DO 180 i = 1, m
280  work( i ) = zero
281  180 CONTINUE
282  DO 200 j = 1, n
283  DO 190 i = 1, min( m, j )
284  work( i ) = work( i ) + abs( a( i, j ) )
285  190 CONTINUE
286  200 CONTINUE
287  END IF
288  ELSE
289  IF( lsame( diag, 'U' ) ) THEN
290  DO 210 i = 1, n
291  work( i ) = one
292  210 CONTINUE
293  DO 220 i = n + 1, m
294  work( i ) = zero
295  220 CONTINUE
296  DO 240 j = 1, n
297  DO 230 i = j + 1, m
298  work( i ) = work( i ) + abs( a( i, j ) )
299  230 CONTINUE
300  240 CONTINUE
301  ELSE
302  DO 250 i = 1, m
303  work( i ) = zero
304  250 CONTINUE
305  DO 270 j = 1, n
306  DO 260 i = j, m
307  work( i ) = work( i ) + abs( a( i, j ) )
308  260 CONTINUE
309  270 CONTINUE
310  END IF
311  END IF
312  VALUE = zero
313  DO 280 i = 1, m
314  sum = work( i )
315  IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
316  280 CONTINUE
317  ELSE IF( ( lsame( norm, 'F' ) ) .OR. ( lsame( norm, 'E' ) ) ) THEN
318 *
319 * Find normF(A).
320 * SSQ(1) is scale
321 * SSQ(2) is sum-of-squares
322 * For better accuracy, sum each column separately.
323 *
324  IF( lsame( uplo, 'U' ) ) THEN
325  IF( lsame( diag, 'U' ) ) THEN
326  ssq( 1 ) = one
327  ssq( 2 ) = min( m, n )
328  DO 290 j = 2, n
329  colssq( 1 ) = zero
330  colssq( 2 ) = one
331  CALL zlassq( min( m, j-1 ), a( 1, j ), 1,
332  $ colssq( 1 ), colssq( 2 ) )
333  CALL dcombssq( ssq, colssq )
334  290 CONTINUE
335  ELSE
336  ssq( 1 ) = zero
337  ssq( 2 ) = one
338  DO 300 j = 1, n
339  colssq( 1 ) = zero
340  colssq( 2 ) = one
341  CALL zlassq( min( m, j ), a( 1, j ), 1,
342  $ colssq( 1 ), colssq( 2 ) )
343  CALL dcombssq( ssq, colssq )
344  300 CONTINUE
345  END IF
346  ELSE
347  IF( lsame( diag, 'U' ) ) THEN
348  ssq( 1 ) = one
349  ssq( 2 ) = min( m, n )
350  DO 310 j = 1, n
351  colssq( 1 ) = zero
352  colssq( 2 ) = one
353  CALL zlassq( m-j, a( min( m, j+1 ), j ), 1,
354  $ colssq( 1 ), colssq( 2 ) )
355  CALL dcombssq( ssq, colssq )
356  310 CONTINUE
357  ELSE
358  ssq( 1 ) = zero
359  ssq( 2 ) = one
360  DO 320 j = 1, n
361  colssq( 1 ) = zero
362  colssq( 2 ) = one
363  CALL zlassq( m-j+1, a( j, j ), 1,
364  $ colssq( 1 ), colssq( 2 ) )
365  CALL dcombssq( ssq, colssq )
366  320 CONTINUE
367  END IF
368  END IF
369  VALUE = ssq( 1 )*sqrt( ssq( 2 ) )
370  END IF
371 *
372  zlantr = VALUE
373  RETURN
374 *
375 * End of ZLANTR
376 *
377  END
zlassq
subroutine zlassq(N, X, INCX, SCALE, SUMSQ)
ZLASSQ updates a sum of squares represented in scaled form.
Definition: zlassq.f:108
disnan
logical function disnan(DIN)
DISNAN tests input for NaN.
Definition: disnan.f:61
lsame
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
zlantr
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:144
dcombssq
subroutine dcombssq(V1, V2)
DCOMBSSQ adds two scaled sum of squares quantities.
Definition: dcombssq.f:62