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