LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlantr()

double precision function dlantr ( character  norm,
character  uplo,
character  diag,
integer  m,
integer  n,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( * )  work 
)

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.

Download DLANTR + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DLANTR  returns the value of the one norm,  or the Frobenius norm, or
 the  infinity norm,  or the  element of  largest absolute value  of a
 trapezoidal or triangular matrix A.
Returns
DLANTR
    DLANTR = ( max(abs(A(i,j))), NORM = 'M' or 'm'
             (
             ( norm1(A),         NORM = '1', 'O' or 'o'
             (
             ( normI(A),         NORM = 'I' or 'i'
             (
             ( normF(A),         NORM = 'F', 'f', 'E' or 'e'

 where  norm1  denotes the  one norm of a matrix (maximum column sum),
 normI  denotes the  infinity norm  of a matrix  (maximum row sum) and
 normF  denotes the  Frobenius norm of a matrix (square root of sum of
 squares).  Note that  max(abs(A(i,j)))  is not a consistent matrix norm.
Parameters
[in]NORM
          NORM is CHARACTER*1
          Specifies the value to be returned in DLANTR as described
          above.
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the matrix A is upper or lower trapezoidal.
          = 'U':  Upper trapezoidal
          = 'L':  Lower trapezoidal
          Note that A is triangular instead of trapezoidal if M = N.
[in]DIAG
          DIAG is CHARACTER*1
          Specifies whether or not the matrix A has unit diagonal.
          = 'N':  Non-unit diagonal
          = 'U':  Unit diagonal
[in]M
          M is INTEGER
          The number of rows of the matrix A.  M >= 0, and if
          UPLO = 'U', M <= N.  When M = 0, DLANTR is set to zero.
[in]N
          N is INTEGER
          The number of columns of the matrix A.  N >= 0, and if
          UPLO = 'L', N <= M.  When N = 0, DLANTR is set to zero.
[in]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          The trapezoidal matrix A (A is triangular if M = N).
          If UPLO = 'U', the leading m by n upper trapezoidal part of
          the array A contains the upper trapezoidal matrix, and the
          strictly lower triangular part of A is not referenced.
          If UPLO = 'L', the leading m by n lower trapezoidal part of
          the array A contains the lower trapezoidal matrix, and the
          strictly upper triangular part of A is not referenced.  Note
          that when DIAG = 'U', the diagonal elements of A are not
          referenced and are assumed to be one.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(M,1).
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK)),
          where LWORK >= M when NORM = 'I'; otherwise, WORK is not
          referenced.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 139 of file dlantr.f.

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 A( LDA, * ), WORK( * )
152* ..
153*
154* =====================================================================
155*
156* .. Parameters ..
157 DOUBLE PRECISION ONE, ZERO
158 parameter( one = 1.0d+0, zero = 0.0d+0 )
159* ..
160* .. Local Scalars ..
161 LOGICAL UDIAG
162 INTEGER I, J
163 DOUBLE PRECISION SCALE, SUM, VALUE
164* ..
165* .. External Subroutines ..
166 EXTERNAL dlassq
167* ..
168* .. External Functions ..
169 LOGICAL LSAME, DISNAN
170 EXTERNAL lsame, disnan
171* ..
172* .. Intrinsic Functions ..
173 INTRINSIC abs, min, sqrt
174* ..
175* .. Executable Statements ..
176*
177 IF( min( m, n ).EQ.0 ) THEN
178 VALUE = zero
179 ELSE IF( lsame( norm, 'M' ) ) THEN
180*
181* Find max(abs(A(i,j))).
182*
183 IF( lsame( diag, 'U' ) ) THEN
184 VALUE = one
185 IF( lsame( uplo, 'U' ) ) THEN
186 DO 20 j = 1, n
187 DO 10 i = 1, min( m, j-1 )
188 sum = abs( a( i, j ) )
189 IF( VALUE .LT. sum .OR. 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. disnan( sum ) ) VALUE = sum
197 30 CONTINUE
198 40 CONTINUE
199 END IF
200 ELSE
201 VALUE = zero
202 IF( lsame( uplo, 'U' ) ) THEN
203 DO 60 j = 1, n
204 DO 50 i = 1, min( m, j )
205 sum = abs( a( i, j ) )
206 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
207 50 CONTINUE
208 60 CONTINUE
209 ELSE
210 DO 80 j = 1, n
211 DO 70 i = j, m
212 sum = abs( a( i, j ) )
213 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
214 70 CONTINUE
215 80 CONTINUE
216 END IF
217 END IF
218 ELSE IF( ( lsame( norm, 'O' ) ) .OR. ( norm.EQ.'1' ) ) THEN
219*
220* Find norm1(A).
221*
222 VALUE = zero
223 udiag = lsame( diag, 'U' )
224 IF( lsame( uplo, 'U' ) ) THEN
225 DO 110 j = 1, n
226 IF( ( udiag ) .AND. ( j.LE.m ) ) THEN
227 sum = one
228 DO 90 i = 1, j - 1
229 sum = sum + abs( a( i, j ) )
230 90 CONTINUE
231 ELSE
232 sum = zero
233 DO 100 i = 1, min( m, j )
234 sum = sum + abs( a( i, j ) )
235 100 CONTINUE
236 END IF
237 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
238 110 CONTINUE
239 ELSE
240 DO 140 j = 1, n
241 IF( udiag ) THEN
242 sum = one
243 DO 120 i = j + 1, m
244 sum = sum + abs( a( i, j ) )
245 120 CONTINUE
246 ELSE
247 sum = zero
248 DO 130 i = j, m
249 sum = sum + abs( a( i, j ) )
250 130 CONTINUE
251 END IF
252 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
253 140 CONTINUE
254 END IF
255 ELSE IF( lsame( norm, 'I' ) ) THEN
256*
257* Find normI(A).
258*
259 IF( lsame( uplo, 'U' ) ) THEN
260 IF( lsame( diag, 'U' ) ) THEN
261 DO 150 i = 1, m
262 work( i ) = one
263 150 CONTINUE
264 DO 170 j = 1, n
265 DO 160 i = 1, min( m, j-1 )
266 work( i ) = work( i ) + abs( a( i, j ) )
267 160 CONTINUE
268 170 CONTINUE
269 ELSE
270 DO 180 i = 1, m
271 work( i ) = zero
272 180 CONTINUE
273 DO 200 j = 1, n
274 DO 190 i = 1, min( m, j )
275 work( i ) = work( i ) + abs( a( i, j ) )
276 190 CONTINUE
277 200 CONTINUE
278 END IF
279 ELSE
280 IF( lsame( diag, 'U' ) ) THEN
281 DO 210 i = 1, min( m, n )
282 work( i ) = one
283 210 CONTINUE
284 DO 220 i = n + 1, m
285 work( i ) = zero
286 220 CONTINUE
287 DO 240 j = 1, n
288 DO 230 i = j + 1, m
289 work( i ) = work( i ) + abs( a( i, j ) )
290 230 CONTINUE
291 240 CONTINUE
292 ELSE
293 DO 250 i = 1, m
294 work( i ) = zero
295 250 CONTINUE
296 DO 270 j = 1, n
297 DO 260 i = j, m
298 work( i ) = work( i ) + abs( a( i, j ) )
299 260 CONTINUE
300 270 CONTINUE
301 END IF
302 END IF
303 VALUE = zero
304 DO 280 i = 1, m
305 sum = work( i )
306 IF( VALUE .LT. sum .OR. disnan( sum ) ) VALUE = sum
307 280 CONTINUE
308 ELSE IF( ( lsame( norm, 'F' ) ) .OR. ( lsame( norm, 'E' ) ) ) THEN
309*
310* Find normF(A).
311*
312 IF( lsame( uplo, 'U' ) ) THEN
313 IF( lsame( diag, 'U' ) ) THEN
314 scale = one
315 sum = min( m, n )
316 DO 290 j = 2, n
317 CALL dlassq( min( m, j-1 ), a( 1, j ), 1, scale, sum )
318 290 CONTINUE
319 ELSE
320 scale = zero
321 sum = one
322 DO 300 j = 1, n
323 CALL dlassq( min( m, j ), a( 1, j ), 1, scale, sum )
324 300 CONTINUE
325 END IF
326 ELSE
327 IF( lsame( diag, 'U' ) ) THEN
328 scale = one
329 sum = min( m, n )
330 DO 310 j = 1, n
331 CALL dlassq( m-j, a( min( m, j+1 ), j ), 1, scale,
332 $ sum )
333 310 CONTINUE
334 ELSE
335 scale = zero
336 sum = one
337 DO 320 j = 1, n
338 CALL dlassq( m-j+1, a( j, j ), 1, scale, sum )
339 320 CONTINUE
340 END IF
341 END IF
342 VALUE = scale*sqrt( sum )
343 END IF
344*
345 dlantr = VALUE
346 RETURN
347*
348* End of DLANTR
349*
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
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:141
subroutine dlassq(n, x, incx, scale, sumsq)
DLASSQ updates a sum of squares represented in scaled form.
Definition dlassq.f90:124
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: