ENH: Improving the travis dashboard name
[platform/upstream/lapack.git] / SRC / slansp.f
1 *> \brief \b SLANSP returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a symmetric matrix supplied in packed form.
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SLANSP + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slansp.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slansp.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slansp.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       REAL             FUNCTION SLANSP( NORM, UPLO, N, AP, WORK )
22 *
23 *       .. Scalar Arguments ..
24 *       CHARACTER          NORM, UPLO
25 *       INTEGER            N
26 *       ..
27 *       .. Array Arguments ..
28 *       REAL               AP( * ), WORK( * )
29 *       ..
30 *
31 *
32 *> \par Purpose:
33 *  =============
34 *>
35 *> \verbatim
36 *>
37 *> SLANSP  returns the value of the one norm,  or the Frobenius norm, or
38 *> the  infinity norm,  or the  element of  largest absolute value  of a
39 *> real symmetric matrix A,  supplied in packed form.
40 *> \endverbatim
41 *>
42 *> \return SLANSP
43 *> \verbatim
44 *>
45 *>    SLANSP = ( max(abs(A(i,j))), NORM = 'M' or 'm'
46 *>             (
47 *>             ( norm1(A),         NORM = '1', 'O' or 'o'
48 *>             (
49 *>             ( normI(A),         NORM = 'I' or 'i'
50 *>             (
51 *>             ( normF(A),         NORM = 'F', 'f', 'E' or 'e'
52 *>
53 *> where  norm1  denotes the  one norm of a matrix (maximum column sum),
54 *> normI  denotes the  infinity norm  of a matrix  (maximum row sum) and
55 *> normF  denotes the  Frobenius norm of a matrix (square root of sum of
56 *> squares).  Note that  max(abs(A(i,j)))  is not a consistent matrix norm.
57 *> \endverbatim
58 *
59 *  Arguments:
60 *  ==========
61 *
62 *> \param[in] NORM
63 *> \verbatim
64 *>          NORM is CHARACTER*1
65 *>          Specifies the value to be returned in SLANSP as described
66 *>          above.
67 *> \endverbatim
68 *>
69 *> \param[in] UPLO
70 *> \verbatim
71 *>          UPLO is CHARACTER*1
72 *>          Specifies whether the upper or lower triangular part of the
73 *>          symmetric matrix A is supplied.
74 *>          = 'U':  Upper triangular part of A is supplied
75 *>          = 'L':  Lower triangular part of A is supplied
76 *> \endverbatim
77 *>
78 *> \param[in] N
79 *> \verbatim
80 *>          N is INTEGER
81 *>          The order of the matrix A.  N >= 0.  When N = 0, SLANSP is
82 *>          set to zero.
83 *> \endverbatim
84 *>
85 *> \param[in] AP
86 *> \verbatim
87 *>          AP is REAL array, dimension (N*(N+1)/2)
88 *>          The upper or lower triangle of the symmetric matrix A, packed
89 *>          columnwise in a linear array.  The j-th column of A is stored
90 *>          in the array AP as follows:
91 *>          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
92 *>          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
93 *> \endverbatim
94 *>
95 *> \param[out] WORK
96 *> \verbatim
97 *>          WORK is REAL array, dimension (MAX(1,LWORK)),
98 *>          where LWORK >= N when NORM = 'I' or '1' or 'O'; otherwise,
99 *>          WORK is not referenced.
100 *> \endverbatim
101 *
102 *  Authors:
103 *  ========
104 *
105 *> \author Univ. of Tennessee
106 *> \author Univ. of California Berkeley
107 *> \author Univ. of Colorado Denver
108 *> \author NAG Ltd.
109 *
110 *> \date September 2012
111 *
112 *> \ingroup realOTHERauxiliary
113 *
114 *  =====================================================================
115       REAL             FUNCTION SLANSP( NORM, UPLO, N, AP, WORK )
116 *
117 *  -- LAPACK auxiliary routine (version 3.4.2) --
118 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
119 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120 *     September 2012
121 *
122 *     .. Scalar Arguments ..
123       CHARACTER          NORM, UPLO
124       INTEGER            N
125 *     ..
126 *     .. Array Arguments ..
127       REAL               AP( * ), WORK( * )
128 *     ..
129 *
130 * =====================================================================
131 *
132 *     .. Parameters ..
133       REAL               ONE, ZERO
134       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
135 *     ..
136 *     .. Local Scalars ..
137       INTEGER            I, J, K
138       REAL               ABSA, SCALE, SUM, VALUE
139 *     ..
140 *     .. External Subroutines ..
141       EXTERNAL           SLASSQ
142 *     ..
143 *     .. External Functions ..
144       LOGICAL            LSAME, SISNAN
145       EXTERNAL           LSAME, SISNAN
146 *     ..
147 *     .. Intrinsic Functions ..
148       INTRINSIC          ABS, SQRT
149 *     ..
150 *     .. Executable Statements ..
151 *
152       IF( N.EQ.0 ) THEN
153          VALUE = ZERO
154       ELSE IF( LSAME( NORM, 'M' ) ) THEN
155 *
156 *        Find max(abs(A(i,j))).
157 *
158          VALUE = ZERO
159          IF( LSAME( UPLO, 'U' ) ) THEN
160             K = 1
161             DO 20 J = 1, N
162                DO 10 I = K, K + J - 1
163                   SUM = ABS( AP( I ) )
164                   IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
165    10          CONTINUE
166                K = K + J
167    20       CONTINUE
168          ELSE
169             K = 1
170             DO 40 J = 1, N
171                DO 30 I = K, K + N - J
172                   SUM = ABS( AP( I ) )
173                   IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
174    30          CONTINUE
175                K = K + N - J + 1
176    40       CONTINUE
177          END IF
178       ELSE IF( ( LSAME( NORM, 'I' ) ) .OR. ( LSAME( NORM, 'O' ) ) .OR.
179      $         ( NORM.EQ.'1' ) ) THEN
180 *
181 *        Find normI(A) ( = norm1(A), since A is symmetric).
182 *
183          VALUE = ZERO
184          K = 1
185          IF( LSAME( UPLO, 'U' ) ) THEN
186             DO 60 J = 1, N
187                SUM = ZERO
188                DO 50 I = 1, J - 1
189                   ABSA = ABS( AP( K ) )
190                   SUM = SUM + ABSA
191                   WORK( I ) = WORK( I ) + ABSA
192                   K = K + 1
193    50          CONTINUE
194                WORK( J ) = SUM + ABS( AP( K ) )
195                K = K + 1
196    60       CONTINUE
197             DO 70 I = 1, N
198                SUM = WORK( I )
199                IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
200    70       CONTINUE
201          ELSE
202             DO 80 I = 1, N
203                WORK( I ) = ZERO
204    80       CONTINUE
205             DO 100 J = 1, N
206                SUM = WORK( J ) + ABS( AP( K ) )
207                K = K + 1
208                DO 90 I = J + 1, N
209                   ABSA = ABS( AP( K ) )
210                   SUM = SUM + ABSA
211                   WORK( I ) = WORK( I ) + ABSA
212                   K = K + 1
213    90          CONTINUE
214                IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
215   100       CONTINUE
216          END IF
217       ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
218 *
219 *        Find normF(A).
220 *
221          SCALE = ZERO
222          SUM = ONE
223          K = 2
224          IF( LSAME( UPLO, 'U' ) ) THEN
225             DO 110 J = 2, N
226                CALL SLASSQ( J-1, AP( K ), 1, SCALE, SUM )
227                K = K + J
228   110       CONTINUE
229          ELSE
230             DO 120 J = 1, N - 1
231                CALL SLASSQ( N-J, AP( K ), 1, SCALE, SUM )
232                K = K + N - J + 1
233   120       CONTINUE
234          END IF
235          SUM = 2*SUM
236          K = 1
237          DO 130 I = 1, N
238             IF( AP( K ).NE.ZERO ) THEN
239                ABSA = ABS( AP( K ) )
240                IF( SCALE.LT.ABSA ) THEN
241                   SUM = ONE + SUM*( SCALE / ABSA )**2
242                   SCALE = ABSA
243                ELSE
244                   SUM = SUM + ( ABSA / SCALE )**2
245                END IF
246             END IF
247             IF( LSAME( UPLO, 'U' ) ) THEN
248                K = K + I + 1
249             ELSE
250                K = K + N - I + 1
251             END IF
252   130    CONTINUE
253          VALUE = SCALE*SQRT( SUM )
254       END IF
255 *
256       SLANSP = VALUE
257       RETURN
258 *
259 *     End of SLANSP
260 *
261       END