LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ slantr()

real function slantr ( character  NORM,
character  UPLO,
character  DIAG,
integer  M,
integer  N,
real, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  WORK 
)

SLANTR 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 SLANTR + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 SLANTR  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
SLANTR
    SLANTR = ( 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 SLANTR 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, SLANTR 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, SLANTR is set to zero.
[in]A
          A is REAL 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 REAL 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.
Date
December 2016

Definition at line 143 of file slantr.f.

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  REAL A( LDA, * ), WORK( * )
156 * ..
157 *
158 * =====================================================================
159 *
160 * .. Parameters ..
161  REAL ONE, ZERO
162  parameter( one = 1.0e+0, zero = 0.0e+0 )
163 * ..
164 * .. Local Scalars ..
165  LOGICAL UDIAG
166  INTEGER I, J
167  REAL SUM, VALUE
168 * ..
169 * .. Local Arrays ..
170  REAL SSQ( 2 ), COLSSQ( 2 )
171 * ..
172 * .. External Functions ..
173  LOGICAL LSAME, SISNAN
174  EXTERNAL lsame, sisnan
175 * ..
176 * .. External Subroutines ..
177  EXTERNAL slassq, scombssq
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. sisnan( 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. sisnan( 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. sisnan( 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. sisnan( 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. sisnan( 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. sisnan( 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. sisnan( 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 slassq( min( m, j-1 ), a( 1, j ), 1,
330  $ colssq( 1 ), colssq( 2 ) )
331  CALL scombssq( 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 slassq( min( m, j ), a( 1, j ), 1,
340  $ colssq( 1 ), colssq( 2 ) )
341  CALL scombssq( 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 slassq( m-j, a( min( m, j+1 ), j ), 1,
352  $ colssq( 1 ), colssq( 2 ) )
353  CALL scombssq( 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 slassq( m-j+1, a( j, j ), 1,
362  $ colssq( 1 ), colssq( 2 ) )
363  CALL scombssq( ssq, colssq )
364  320 CONTINUE
365  END IF
366  END IF
367  VALUE = ssq( 1 )*sqrt( ssq( 2 ) )
368  END IF
369 *
370  slantr = VALUE
371  RETURN
372 *
373 * End of SLANTR
374 *
Here is the call graph for this function:
slassq
subroutine slassq(N, X, INCX, SCALE, SUMSQ)
SLASSQ updates a sum of squares represented in scaled form.
Definition: slassq.f:105
sisnan
logical function sisnan(SIN)
SISNAN tests input for NaN.
Definition: sisnan.f:61
slantr
real function slantr(NORM, UPLO, DIAG, M, N, A, LDA, WORK)
SLANTR returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition: slantr.f:143
lsame
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
scombssq
subroutine scombssq(V1, V2)
SCOMBSSQ adds two scaled sum of squares quantities
Definition: scombssq.f:62