LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ zlantp()

double precision function zlantp ( character  NORM,
character  UPLO,
character  DIAG,
integer  N,
complex*16, dimension( * )  AP,
double precision, dimension( * )  WORK 
)

ZLANTP returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a triangular matrix supplied in packed form.

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

Purpose:
 ZLANTP  returns the value of the one norm,  or the Frobenius norm, or
 the  infinity norm,  or the  element of  largest absolute value  of a
 triangular matrix A, supplied in packed form.
Returns
ZLANTP
    ZLANTP = ( 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 ZLANTP as described
          above.
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the matrix A is upper or lower triangular.
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]DIAG
          DIAG is CHARACTER*1
          Specifies whether or not the matrix A is unit triangular.
          = 'N':  Non-unit triangular
          = 'U':  Unit triangular
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.  When N = 0, ZLANTP is
          set to zero.
[in]AP
          AP is COMPLEX*16 array, dimension (N*(N+1)/2)
          The upper or lower triangular matrix A, packed columnwise in
          a linear array.  The j-th column of A is stored in the array
          AP as follows:
          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
          Note that when DIAG = 'U', the elements of the array AP
          corresponding to the diagonal elements of the matrix A are
          not referenced, but are assumed to be one.
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK)),
          where LWORK >= N 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 127 of file zlantp.f.

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