1*> \brief \b SLANHS returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value of any element of an upper Hessenberg matrix.
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SLANHS + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slanhs.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slanhs.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slanhs.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       REAL             FUNCTION SLANHS( NORM, N, A, LDA, WORK )
22*
23*       .. Scalar Arguments ..
24*       CHARACTER          NORM
25*       INTEGER            LDA, N
26*       ..
27*       .. Array Arguments ..
28*       REAL               A( LDA, * ), WORK( * )
29*       ..
30*
31*
32*> \par Purpose:
33*  =============
34*>
35*> \verbatim
36*>
37*> SLANHS  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*> Hessenberg matrix A.
40*> \endverbatim
41*>
42*> \return SLANHS
43*> \verbatim
44*>
45*>    SLANHS = ( 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 SLANHS as described
66*>          above.
67*> \endverbatim
68*>
69*> \param[in] N
70*> \verbatim
71*>          N is INTEGER
72*>          The order of the matrix A.  N >= 0.  When N = 0, SLANHS is
73*>          set to zero.
74*> \endverbatim
75*>
76*> \param[in] A
77*> \verbatim
78*>          A is REAL array, dimension (LDA,N)
79*>          The n by n upper Hessenberg matrix A; the part of A below the
80*>          first sub-diagonal is not referenced.
81*> \endverbatim
82*>
83*> \param[in] LDA
84*> \verbatim
85*>          LDA is INTEGER
86*>          The leading dimension of the array A.  LDA >= max(N,1).
87*> \endverbatim
88*>
89*> \param[out] WORK
90*> \verbatim
91*>          WORK is REAL array, dimension (MAX(1,LWORK)),
92*>          where LWORK >= N when NORM = 'I'; otherwise, WORK is not
93*>          referenced.
94*> \endverbatim
95*
96*  Authors:
97*  ========
98*
99*> \author Univ. of Tennessee
100*> \author Univ. of California Berkeley
101*> \author Univ. of Colorado Denver
102*> \author NAG Ltd.
103*
104*> \ingroup realOTHERauxiliary
105*
106*  =====================================================================
107      REAL             FUNCTION SLANHS( NORM, N, A, LDA, WORK )
108*
109*  -- LAPACK auxiliary routine --
110*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
111*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
112*
113      IMPLICIT NONE
114*     .. Scalar Arguments ..
115      CHARACTER          NORM
116      INTEGER            LDA, N
117*     ..
118*     .. Array Arguments ..
119      REAL               A( LDA, * ), WORK( * )
120*     ..
121*
122* =====================================================================
123*
124*     .. Parameters ..
125      REAL               ONE, ZERO
126      PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
127*     ..
128*     .. Local Scalars ..
129      INTEGER            I, J
130      REAL               SUM, VALUE
131*     ..
132*     .. Local Arrays ..
133      REAL               SSQ( 2 ), COLSSQ( 2 )
134*     ..
135*     .. External Functions ..
136      LOGICAL            LSAME, SISNAN
137      EXTERNAL           LSAME, SISNAN
138*     ..
139*     .. External Subroutines ..
140      EXTERNAL           SLASSQ, SCOMBSSQ
141*     ..
142*     .. Intrinsic Functions ..
143      INTRINSIC          ABS, MIN, SQRT
144*     ..
145*     .. Executable Statements ..
146*
147      IF( N.EQ.0 ) THEN
148         VALUE = ZERO
149      ELSE IF( LSAME( NORM, 'M' ) ) THEN
150*
151*        Find max(abs(A(i,j))).
152*
153         VALUE = ZERO
154         DO 20 J = 1, N
155            DO 10 I = 1, MIN( N, J+1 )
156               SUM = ABS( A( I, J ) )
157               IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
158   10       CONTINUE
159   20    CONTINUE
160      ELSE IF( ( LSAME( NORM, 'O' ) ) .OR. ( NORM.EQ.'1' ) ) THEN
161*
162*        Find norm1(A).
163*
164         VALUE = ZERO
165         DO 40 J = 1, N
166            SUM = ZERO
167            DO 30 I = 1, MIN( N, J+1 )
168               SUM = SUM + ABS( A( I, J ) )
169   30       CONTINUE
170            IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
171   40    CONTINUE
172      ELSE IF( LSAME( NORM, 'I' ) ) THEN
173*
174*        Find normI(A).
175*
176         DO 50 I = 1, N
177            WORK( I ) = ZERO
178   50    CONTINUE
179         DO 70 J = 1, N
180            DO 60 I = 1, MIN( N, J+1 )
181               WORK( I ) = WORK( I ) + ABS( A( I, J ) )
182   60       CONTINUE
183   70    CONTINUE
184         VALUE = ZERO
185         DO 80 I = 1, N
186            SUM = WORK( I )
187            IF( VALUE .LT. SUM .OR. SISNAN( SUM ) ) VALUE = SUM
188   80    CONTINUE
189      ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
190*
191*        Find normF(A).
192*        SSQ(1) is scale
193*        SSQ(2) is sum-of-squares
194*        For better accuracy, sum each column separately.
195*
196         SSQ( 1 ) = ZERO
197         SSQ( 2 ) = ONE
198         DO 90 J = 1, N
199            COLSSQ( 1 ) = ZERO
200            COLSSQ( 2 ) = ONE
201            CALL SLASSQ( MIN( N, J+1 ), A( 1, J ), 1,
202     $                   COLSSQ( 1 ), COLSSQ( 2 ) )
203            CALL SCOMBSSQ( SSQ, COLSSQ )
204   90    CONTINUE
205         VALUE = SSQ( 1 )*SQRT( SSQ( 2 ) )
206      END IF
207*
208      SLANHS = VALUE
209      RETURN
210*
211*     End of SLANHS
212*
213      END
214