source: trunk/SOURCES/BLAS/slange.f @ 23

Last change on this file since 23 was 22, checked in by roche, 9 years ago

Petites adaptations diverses du code pour compilation en gfortran. Ajout d un Makefile flexible a option pour choisir ifort ou gfortran.

File size: 5.4 KB
Line 
1*> \brief \b SLANGE
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at 
6*            http://www.netlib.org/lapack/explore-html/ 
7*
8*> \htmlonly
9*> Download SLANGE + dependencies 
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slange.f"> 
11*> [TGZ]</a> 
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slange.f"> 
13*> [ZIP]</a> 
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slange.f"> 
15*> [TXT]</a>
16*> \endhtmlonly 
17*
18*  Definition:
19*  ===========
20*
21*       REAL             FUNCTION SLANGE( NORM, M, N, A, LDA, WORK )
22* 
23*       .. Scalar Arguments ..
24*       CHARACTER          NORM
25*       INTEGER            LDA, M, N
26*       ..
27*       .. Array Arguments ..
28*       REAL               A( LDA, * ), WORK( * )
29*       ..
30* 
31*
32*> \par Purpose:
33*  =============
34*>
35*> \verbatim
36*>
37*> SLANGE  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 matrix A.
40*> \endverbatim
41*>
42*> \return SLANGE
43*> \verbatim
44*>
45*>    SLANGE = ( 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 SLANGE as described
66*>          above.
67*> \endverbatim
68*>
69*> \param[in] M
70*> \verbatim
71*>          M is INTEGER
72*>          The number of rows of the matrix A.  M >= 0.  When M = 0,
73*>          SLANGE is set to zero.
74*> \endverbatim
75*>
76*> \param[in] N
77*> \verbatim
78*>          N is INTEGER
79*>          The number of columns of the matrix A.  N >= 0.  When N = 0,
80*>          SLANGE is set to zero.
81*> \endverbatim
82*>
83*> \param[in] A
84*> \verbatim
85*>          A is REAL array, dimension (LDA,N)
86*>          The m by n matrix A.
87*> \endverbatim
88*>
89*> \param[in] LDA
90*> \verbatim
91*>          LDA is INTEGER
92*>          The leading dimension of the array A.  LDA >= max(M,1).
93*> \endverbatim
94*>
95*> \param[out] WORK
96*> \verbatim
97*>          WORK is REAL array, dimension (MAX(1,LWORK)),
98*>          where LWORK >= M when NORM = 'I'; otherwise, WORK is not
99*>          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 November 2011
111*
112*> \ingroup realGEauxiliary
113*
114*  =====================================================================
115      REAL             FUNCTION SLANGE( NORM, M, N, A, LDA, WORK )
116*
117*  -- LAPACK auxiliary routine (version 3.4.0) --
118*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
119*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120*     November 2011
121*
122*     .. Scalar Arguments ..
123      CHARACTER          NORM
124      INTEGER            LDA, M, N
125*     ..
126*     .. Array Arguments ..
127      REAL               A( LDA, * ), 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
138      REAL               SCALE, SUM, VALUE
139*     ..
140*     .. External Subroutines ..
141      EXTERNAL           SLASSQ
142*     ..
143*     .. External Functions ..
144      LOGICAL            LSAME
145      EXTERNAL           LSAME
146*     ..
147*     .. Intrinsic Functions ..
148      INTRINSIC          ABS, MAX, MIN, SQRT
149*     ..
150*     .. Executable Statements ..
151*
152      IF( MIN( M, 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         DO 20 J = 1, N
160            DO 10 I = 1, M
161               VALUE = MAX( VALUE, ABS( A( I, J ) ) )
162   10       CONTINUE
163   20    CONTINUE
164      ELSE IF( ( LSAME( NORM, 'O' ) ) .OR. ( NORM.EQ.'1' ) ) THEN
165*
166*        Find norm1(A).
167*
168         VALUE = ZERO
169         DO 40 J = 1, N
170            SUM = ZERO
171            DO 30 I = 1, M
172               SUM = SUM + ABS( A( I, J ) )
173   30       CONTINUE
174            VALUE = MAX( VALUE, SUM )
175   40    CONTINUE
176      ELSE IF( LSAME( NORM, 'I' ) ) THEN
177*
178*        Find normI(A).
179*
180         DO 50 I = 1, M
181            WORK( I ) = ZERO
182   50    CONTINUE
183         DO 70 J = 1, N
184            DO 60 I = 1, M
185               WORK( I ) = WORK( I ) + ABS( A( I, J ) )
186   60       CONTINUE
187   70    CONTINUE
188         VALUE = ZERO
189         DO 80 I = 1, M
190            VALUE = MAX( VALUE, WORK( I ) )
191   80    CONTINUE
192      ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
193*
194*        Find normF(A).
195*
196         SCALE = ZERO
197         SUM = ONE
198         DO 90 J = 1, N
199            CALL SLASSQ( M, A( 1, J ), 1, SCALE, SUM )
200   90    CONTINUE
201         VALUE = SCALE*SQRT( SUM )
202      END IF
203*
204      SLANGE = VALUE
205      RETURN
206*
207*     End of SLANGE
208*
209      END
Note: See TracBrowser for help on using the repository browser.