STYLE: Remove trailing whitespace in Fortran files
[platform/upstream/lapack.git] / SRC / slantb.f
1 *> \brief \b SLANTB 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 SLANTB + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slantb.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slantb.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slantb.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       REAL             FUNCTION SLANTB( 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               AB( LDAB, * ), WORK( * )
30 *       ..
31 *
32 *
33 *> \par Purpose:
34 *  =============
35 *>
36 *> \verbatim
37 *>
38 *> SLANTB  returns the value of the one norm,  or the Frobenius norm, or
39 *> the  infinity norm,  or the element of  largest absolute value  of an
40 *> n by n triangular band matrix A,  with ( k + 1 ) diagonals.
41 *> \endverbatim
42 *>
43 *> \return SLANTB
44 *> \verbatim
45 *>
46 *>    SLANTB = ( max(abs(A(i,j))), NORM = 'M' or 'm'
47 *>             (
48 *>             ( norm1(A),         NORM = '1', 'O' or 'o'
49 *>             (
50 *>             ( normI(A),         NORM = 'I' or 'i'
51 *>             (
52 *>             ( normF(A),         NORM = 'F', 'f', 'E' or 'e'
53 *>
54 *> where  norm1  denotes the  one norm of a matrix (maximum column sum),
55 *> normI  denotes the  infinity norm  of a matrix  (maximum row sum) and
56 *> normF  denotes the  Frobenius norm of a matrix (square root of sum of
57 *> squares).  Note that  max(abs(A(i,j)))  is not a consistent matrix norm.
58 *> \endverbatim
59 *
60 *  Arguments:
61 *  ==========
62 *
63 *> \param[in] NORM
64 *> \verbatim
65 *>          NORM is CHARACTER*1
66 *>          Specifies the value to be returned in SLANTB as described
67 *>          above.
68 *> \endverbatim
69 *>
70 *> \param[in] UPLO
71 *> \verbatim
72 *>          UPLO is CHARACTER*1
73 *>          Specifies whether the matrix A is upper or lower triangular.
74 *>          = 'U':  Upper triangular
75 *>          = 'L':  Lower triangular
76 *> \endverbatim
77 *>
78 *> \param[in] DIAG
79 *> \verbatim
80 *>          DIAG is CHARACTER*1
81 *>          Specifies whether or not the matrix A is unit triangular.
82 *>          = 'N':  Non-unit triangular
83 *>          = 'U':  Unit triangular
84 *> \endverbatim
85 *>
86 *> \param[in] N
87 *> \verbatim
88 *>          N is INTEGER
89 *>          The order of the matrix A.  N >= 0.  When N = 0, SLANTB is
90 *>          set to zero.
91 *> \endverbatim
92 *>
93 *> \param[in] K
94 *> \verbatim
95 *>          K is INTEGER
96 *>          The number of super-diagonals of the matrix A if UPLO = 'U',
97 *>          or the number of sub-diagonals of the matrix A if UPLO = 'L'.
98 *>          K >= 0.
99 *> \endverbatim
100 *>
101 *> \param[in] AB
102 *> \verbatim
103 *>          AB is REAL array, dimension (LDAB,N)
104 *>          The upper or lower triangular band matrix A, stored in the
105 *>          first k+1 rows of AB.  The j-th column of A is stored
106 *>          in the j-th column of the array AB as follows:
107 *>          if UPLO = 'U', AB(k+1+i-j,j) = A(i,j) for max(1,j-k)<=i<=j;
108 *>          if UPLO = 'L', AB(1+i-j,j)   = A(i,j) for j<=i<=min(n,j+k).
109 *>          Note that when DIAG = 'U', the elements of the array AB
110 *>          corresponding to the diagonal elements of the matrix A are
111 *>          not referenced, but are assumed to be one.
112 *> \endverbatim
113 *>
114 *> \param[in] LDAB
115 *> \verbatim
116 *>          LDAB is INTEGER
117 *>          The leading dimension of the array AB.  LDAB >= K+1.
118 *> \endverbatim
119 *>
120 *> \param[out] WORK
121 *> \verbatim
122 *>          WORK is REAL array, dimension (MAX(1,LWORK)),
123 *>          where LWORK >= N when NORM = 'I'; otherwise, WORK is not
124 *>          referenced.
125 *> \endverbatim
126 *
127 *  Authors:
128 *  ========
129 *
130 *> \author Univ. of Tennessee
131 *> \author Univ. of California Berkeley
132 *> \author Univ. of Colorado Denver
133 *> \author NAG Ltd.
134 *
135 *> \date September 2012
136 *
137 *> \ingroup realOTHERauxiliary
138 *
139 *  =====================================================================
140       REAL             FUNCTION SLANTB( NORM, UPLO, DIAG, N, K, AB,
141      $                 LDAB, WORK )
142 *
143 *  -- LAPACK auxiliary routine (version 3.4.2) --
144 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
145 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146 *     September 2012
147 *
148 *     .. Scalar Arguments ..
149       CHARACTER          DIAG, NORM, UPLO
150       INTEGER            K, LDAB, N
151 *     ..
152 *     .. Array Arguments ..
153       REAL               AB( LDAB, * ), WORK( * )
154 *     ..
155 *
156 * =====================================================================
157 *
158 *     .. Parameters ..
159       REAL               ONE, ZERO
160       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
161 *     ..
162 *     .. Local Scalars ..
163       LOGICAL            UDIAG
164       INTEGER            I, J, L
165       REAL               SCALE, SUM, VALUE
166 *     ..
167 *     .. External Subroutines ..
168       EXTERNAL           SLASSQ
169 *     ..
170 *     .. External Functions ..
171       LOGICAL            LSAME, SISNAN
172       EXTERNAL           LSAME, SISNAN
173 *     ..
174 *     .. Intrinsic Functions ..
175       INTRINSIC          ABS, MAX, MIN, SQRT
176 *     ..
177 *     .. Executable Statements ..
178 *
179       IF( N.EQ.0 ) THEN
180          VALUE = ZERO
181       ELSE IF( LSAME( NORM, 'M' ) ) THEN
182 *
183 *        Find max(abs(A(i,j))).
184 *
185          IF( LSAME( DIAG, 'U' ) ) THEN
186             VALUE = ONE
187             IF( LSAME( UPLO, 'U' ) ) THEN
188                DO 20 J = 1, N
189                   DO 10 I = MAX( K+2-J, 1 ), K
190                      SUM = ABS( AB( I, J ) )
191                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
192    10             CONTINUE
193    20          CONTINUE
194             ELSE
195                DO 40 J = 1, N
196                   DO 30 I = 2, MIN( N+1-J, K+1 )
197                      SUM = ABS( AB( I, J ) )
198                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
199    30             CONTINUE
200    40          CONTINUE
201             END IF
202          ELSE
203             VALUE = ZERO
204             IF( LSAME( UPLO, 'U' ) ) THEN
205                DO 60 J = 1, N
206                   DO 50 I = MAX( K+2-J, 1 ), K + 1
207                      SUM = ABS( AB( I, J ) )
208                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
209    50             CONTINUE
210    60          CONTINUE
211             ELSE
212                DO 80 J = 1, N
213                   DO 70 I = 1, MIN( N+1-J, K+1 )
214                      SUM = ABS( AB( I, J ) )
215                      IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
216    70             CONTINUE
217    80          CONTINUE
218             END IF
219          END IF
220       ELSE IF( ( LSAME( NORM, 'O' ) ) .OR. ( NORM.EQ.'1' ) ) THEN
221 *
222 *        Find norm1(A).
223 *
224          VALUE = ZERO
225          UDIAG = LSAME( DIAG, 'U' )
226          IF( LSAME( UPLO, 'U' ) ) THEN
227             DO 110 J = 1, N
228                IF( UDIAG ) THEN
229                   SUM = ONE
230                   DO 90 I = MAX( K+2-J, 1 ), K
231                      SUM = SUM + ABS( AB( I, J ) )
232    90             CONTINUE
233                ELSE
234                   SUM = ZERO
235                   DO 100 I = MAX( K+2-J, 1 ), K + 1
236                      SUM = SUM + ABS( AB( I, J ) )
237   100             CONTINUE
238                END IF
239                IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
240   110       CONTINUE
241          ELSE
242             DO 140 J = 1, N
243                IF( UDIAG ) THEN
244                   SUM = ONE
245                   DO 120 I = 2, MIN( N+1-J, K+1 )
246                      SUM = SUM + ABS( AB( I, J ) )
247   120             CONTINUE
248                ELSE
249                   SUM = ZERO
250                   DO 130 I = 1, MIN( N+1-J, K+1 )
251                      SUM = SUM + ABS( AB( I, J ) )
252   130             CONTINUE
253                END IF
254                IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
255   140       CONTINUE
256          END IF
257       ELSE IF( LSAME( NORM, 'I' ) ) THEN
258 *
259 *        Find normI(A).
260 *
261          VALUE = ZERO
262          IF( LSAME( UPLO, 'U' ) ) THEN
263             IF( LSAME( DIAG, 'U' ) ) THEN
264                DO 150 I = 1, N
265                   WORK( I ) = ONE
266   150          CONTINUE
267                DO 170 J = 1, N
268                   L = K + 1 - J
269                   DO 160 I = MAX( 1, J-K ), J - 1
270                      WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
271   160             CONTINUE
272   170          CONTINUE
273             ELSE
274                DO 180 I = 1, N
275                   WORK( I ) = ZERO
276   180          CONTINUE
277                DO 200 J = 1, N
278                   L = K + 1 - J
279                   DO 190 I = MAX( 1, J-K ), J
280                      WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
281   190             CONTINUE
282   200          CONTINUE
283             END IF
284          ELSE
285             IF( LSAME( DIAG, 'U' ) ) THEN
286                DO 210 I = 1, N
287                   WORK( I ) = ONE
288   210          CONTINUE
289                DO 230 J = 1, N
290                   L = 1 - J
291                   DO 220 I = J + 1, MIN( N, J+K )
292                      WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
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                   L = 1 - J
301                   DO 250 I = J, MIN( N, J+K )
302                      WORK( I ) = WORK( I ) + ABS( AB( L+I, J ) )
303   250             CONTINUE
304   260          CONTINUE
305             END IF
306          END IF
307          DO 270 I = 1, N
308             SUM = WORK( I )
309             IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
310   270    CONTINUE
311       ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
312 *
313 *        Find normF(A).
314 *
315          IF( LSAME( UPLO, 'U' ) ) THEN
316             IF( LSAME( DIAG, 'U' ) ) THEN
317                SCALE = ONE
318                SUM = N
319                IF( K.GT.0 ) THEN
320                   DO 280 J = 2, N
321                      CALL SLASSQ( MIN( J-1, K ),
322      $                            AB( MAX( K+2-J, 1 ), J ), 1, SCALE,
323      $                            SUM )
324   280             CONTINUE
325                END IF
326             ELSE
327                SCALE = ZERO
328                SUM = ONE
329                DO 290 J = 1, N
330                   CALL SLASSQ( MIN( J, K+1 ), AB( MAX( K+2-J, 1 ), J ),
331      $                         1, SCALE, SUM )
332   290          CONTINUE
333             END IF
334          ELSE
335             IF( LSAME( DIAG, 'U' ) ) THEN
336                SCALE = ONE
337                SUM = N
338                IF( K.GT.0 ) THEN
339                   DO 300 J = 1, N - 1
340                      CALL SLASSQ( MIN( N-J, K ), AB( 2, J ), 1, SCALE,
341      $                            SUM )
342   300             CONTINUE
343                END IF
344             ELSE
345                SCALE = ZERO
346                SUM = ONE
347                DO 310 J = 1, N
348                   CALL SLASSQ( MIN( N-J+1, K+1 ), AB( 1, J ), 1, SCALE,
349      $                         SUM )
350   310          CONTINUE
351             END IF
352          END IF
353          VALUE = SCALE*SQRT( SUM )
354       END IF
355 *
356       SLANTB = VALUE
357       RETURN
358 *
359 *     End of SLANTB
360 *
361       END