Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / clantb.f
1 *> \brief \b CLANTB 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 band matrix.
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CLANTB + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clantb.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clantb.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clantb.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       REAL             FUNCTION CLANTB( NORM, UPLO, DIAG, N, K, AB,
22 *                        LDAB, WORK )
23 *
24 *       .. Scalar Arguments ..
25 *       CHARACTER          DIAG, NORM, UPLO
26 *       INTEGER            K, LDAB, N
27 *       ..
28 *       .. Array Arguments ..
29 *       REAL               WORK( * )
30 *       COMPLEX            AB( LDAB, * )
31 *       ..
32 *
33 *
34 *> \par Purpose:
35 *  =============
36 *>
37 *> \verbatim
38 *>
39 *> CLANTB  returns the value of the one norm,  or the Frobenius norm, or
40 *> the  infinity norm,  or the element of  largest absolute value  of an
41 *> n by n triangular band matrix A,  with ( k + 1 ) diagonals.
42 *> \endverbatim
43 *>
44 *> \return CLANTB
45 *> \verbatim
46 *>
47 *>    CLANTB = ( 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 CLANTB 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 triangular.
75 *>          = 'U':  Upper triangular
76 *>          = 'L':  Lower triangular
77 *> \endverbatim
78 *>
79 *> \param[in] DIAG
80 *> \verbatim
81 *>          DIAG is CHARACTER*1
82 *>          Specifies whether or not the matrix A is unit triangular.
83 *>          = 'N':  Non-unit triangular
84 *>          = 'U':  Unit triangular
85 *> \endverbatim
86 *>
87 *> \param[in] N
88 *> \verbatim
89 *>          N is INTEGER
90 *>          The order of the matrix A.  N >= 0.  When N = 0, CLANTB is
91 *>          set to zero.
92 *> \endverbatim
93 *>
94 *> \param[in] K
95 *> \verbatim
96 *>          K is INTEGER
97 *>          The number of super-diagonals of the matrix A if UPLO = 'U',
98 *>          or the number of sub-diagonals of the matrix A if UPLO = 'L'.
99 *>          K >= 0.
100 *> \endverbatim
101 *>
102 *> \param[in] AB
103 *> \verbatim
104 *>          AB is COMPLEX array, dimension (LDAB,N)
105 *>          The upper or lower triangular band matrix A, stored in the
106 *>          first k+1 rows of AB.  The j-th column of A is stored
107 *>          in the j-th column of the array AB as follows:
108 *>          if UPLO = 'U', AB(k+1+i-j,j) = A(i,j) for max(1,j-k)<=i<=j;
109 *>          if UPLO = 'L', AB(1+i-j,j)   = A(i,j) for j<=i<=min(n,j+k).
110 *>          Note that when DIAG = 'U', the elements of the array AB
111 *>          corresponding to the diagonal elements of the matrix A are
112 *>          not referenced, but are assumed to be one.
113 *> \endverbatim
114 *>
115 *> \param[in] LDAB
116 *> \verbatim
117 *>          LDAB is INTEGER
118 *>          The leading dimension of the array AB.  LDAB >= K+1.
119 *> \endverbatim
120 *>
121 *> \param[out] WORK
122 *> \verbatim
123 *>          WORK is REAL array, dimension (MAX(1,LWORK)),
124 *>          where LWORK >= N 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 September 2012
137 *
138 *> \ingroup complexOTHERauxiliary
139 *
140 *  =====================================================================
141       REAL             FUNCTION CLANTB( NORM, UPLO, DIAG, N, K, AB,
142      $                 LDAB, WORK )
143 *
144 *  -- LAPACK auxiliary routine (version 3.4.2) --
145 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
146 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
147 *     September 2012
148 *
149 *     .. Scalar Arguments ..
150       CHARACTER          DIAG, NORM, UPLO
151       INTEGER            K, LDAB, N
152 *     ..
153 *     .. Array Arguments ..
154       REAL               WORK( * )
155       COMPLEX            AB( LDAB, * )
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, L
167       REAL               SCALE, SUM, VALUE
168 *     ..
169 *     .. External Functions ..
170       LOGICAL            LSAME, SISNAN
171       EXTERNAL           LSAME, SISNAN
172 *     ..
173 *     .. External Subroutines ..
174       EXTERNAL           CLASSQ
175 *     ..
176 *     .. Intrinsic Functions ..
177       INTRINSIC          ABS, MAX, MIN, SQRT
178 *     ..
179 *     .. Executable Statements ..
180 *
181       IF( N.EQ.0 ) THEN
182          VALUE = ZERO
183       ELSE IF( LSAME( NORM, 'M' ) ) THEN
184 *
185 *        Find max(abs(A(i,j))).
186 *
187          IF( LSAME( DIAG, 'U' ) ) THEN
188             VALUE = ONE
189             IF( LSAME( UPLO, 'U' ) ) THEN
190                DO 20 J = 1, N
191                   DO 10 I = MAX( K+2-J, 1 ), K
192                      SUM = ABS( AB( I, J ) )
193                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
194    10             CONTINUE
195    20          CONTINUE
196             ELSE
197                DO 40 J = 1, N
198                   DO 30 I = 2, MIN( N+1-J, K+1 )
199                      SUM = ABS( AB( I, J ) )
200                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
201    30             CONTINUE
202    40          CONTINUE
203             END IF
204          ELSE
205             VALUE = ZERO
206             IF( LSAME( UPLO, 'U' ) ) THEN
207                DO 60 J = 1, N
208                   DO 50 I = MAX( K+2-J, 1 ), K + 1
209                      SUM = ABS( AB( I, J ) )
210                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
211    50             CONTINUE
212    60          CONTINUE
213             ELSE
214                DO 80 J = 1, N
215                   DO 70 I = 1, MIN( N+1-J, K+1 )
216                      SUM = ABS( AB( I, J ) )
217                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
218    70             CONTINUE
219    80          CONTINUE
220             END IF
221          END IF
222       ELSE IF( ( LSAME( NORM, 'O' ) ) .OR. ( NORM.EQ.'1' ) ) THEN
223 *
224 *        Find norm1(A).
225 *
226          VALUE = ZERO
227          UDIAG = LSAME( DIAG, 'U' )
228          IF( LSAME( UPLO, 'U' ) ) THEN
229             DO 110 J = 1, N
230                IF( UDIAG ) THEN
231                   SUM = ONE
232                   DO 90 I = MAX( K+2-J, 1 ), K
233                      SUM = SUM + ABS( AB( I, J ) )
234    90             CONTINUE
235                ELSE
236                   SUM = ZERO
237                   DO 100 I = MAX( K+2-J, 1 ), K + 1
238                      SUM = SUM + ABS( AB( I, J ) )
239   100             CONTINUE
240                END IF
241                IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
242   110       CONTINUE
243          ELSE
244             DO 140 J = 1, N
245                IF( UDIAG ) THEN
246                   SUM = ONE
247                   DO 120 I = 2, MIN( N+1-J, K+1 )
248                      SUM = SUM + ABS( AB( I, J ) )
249   120             CONTINUE
250                ELSE
251                   SUM = ZERO
252                   DO 130 I = 1, MIN( N+1-J, K+1 )
253                      SUM = SUM + ABS( AB( I, J ) )
254   130             CONTINUE
255                END IF
256                IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
257   140       CONTINUE
258          END IF
259       ELSE IF( LSAME( NORM, 'I' ) ) THEN
260 *
261 *        Find normI(A).
262 *
263          VALUE = ZERO
264          IF( LSAME( UPLO, 'U' ) ) THEN
265             IF( LSAME( DIAG, 'U' ) ) THEN
266                DO 150 I = 1, N
267                   WORK( I ) = ONE
268   150          CONTINUE
269                DO 170 J = 1, N
270                   L = K + 1 - J
271                   DO 160 I = MAX( 1, J-K ), J - 1
272                      WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
273   160             CONTINUE
274   170          CONTINUE
275             ELSE
276                DO 180 I = 1, N
277                   WORK( I ) = ZERO
278   180          CONTINUE
279                DO 200 J = 1, N
280                   L = K + 1 - J
281                   DO 190 I = MAX( 1, J-K ), J
282                      WORK( I ) = WORK( I ) + ABS( AB( L+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 230 J = 1, N
292                   L = 1 - J
293                   DO 220 I = J + 1, MIN( N, J+K )
294                      WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
295   220             CONTINUE
296   230          CONTINUE
297             ELSE
298                DO 240 I = 1, N
299                   WORK( I ) = ZERO
300   240          CONTINUE
301                DO 260 J = 1, N
302                   L = 1 - J
303                   DO 250 I = J, MIN( N, J+K )
304                      WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
305   250             CONTINUE
306   260          CONTINUE
307             END IF
308          END IF
309          DO 270 I = 1, N
310             SUM = WORK( I )
311             IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
312   270    CONTINUE
313       ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
314 *
315 *        Find normF(A).
316 *
317          IF( LSAME( UPLO, 'U' ) ) THEN
318             IF( LSAME( DIAG, 'U' ) ) THEN
319                SCALE = ONE
320                SUM = N
321                IF( K.GT.0 ) THEN
322                   DO 280 J = 2, N
323                      CALL CLASSQ( MIN( J-1, K ),
324      $                            AB( MAX( K+2-J, 1 ), J ), 1, SCALE,
325      $                            SUM )
326   280             CONTINUE
327                END IF
328             ELSE
329                SCALE = ZERO
330                SUM = ONE
331                DO 290 J = 1, N
332                   CALL CLASSQ( MIN( J, K+1 ), AB( MAX( K+2-J, 1 ), J ),
333      $                         1, SCALE, SUM )
334   290          CONTINUE
335             END IF
336          ELSE
337             IF( LSAME( DIAG, 'U' ) ) THEN
338                SCALE = ONE
339                SUM = N
340                IF( K.GT.0 ) THEN
341                   DO 300 J = 1, N - 1
342                      CALL CLASSQ( MIN( N-J, K ), AB( 2, J ), 1, SCALE,
343      $                            SUM )
344   300             CONTINUE
345                END IF
346             ELSE
347                SCALE = ZERO
348                SUM = ONE
349                DO 310 J = 1, N
350                   CALL CLASSQ( MIN( N-J+1, K+1 ), AB( 1, J ), 1, SCALE,
351      $                         SUM )
352   310          CONTINUE
353             END IF
354          END IF
355          VALUE = SCALE*SQRT( SUM )
356       END IF
357 *
358       CLANTB = VALUE
359       RETURN
360 *
361 *     End of CLANTB
362 *
363       END