1 *> \brief \b CLASSQ updates a sum of squares represented in scaled form.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLASSQ + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/classq.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/classq.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/classq.f">
21 * SUBROUTINE CLASSQ( N, X, INCX, SCALE, SUMSQ )
23 * .. Scalar Arguments ..
27 * .. Array Arguments ..
37 *> CLASSQ returns the values scl and ssq such that
39 *> ( scl**2 )*ssq = x( 1 )**2 +...+ x( n )**2 + ( scale**2 )*sumsq,
41 *> where x( i ) = abs( X( 1 + ( i - 1 )*INCX ) ). The value of sumsq is
42 *> assumed to be at least unity and the value of ssq will then satisfy
44 *> 1.0 .le. ssq .le. ( sumsq + 2*n ).
46 *> scale is assumed to be non-negative and scl returns the value
48 *> scl = max( scale, abs( real( x( i ) ) ), abs( aimag( x( i ) ) ) ),
51 *> scale and sumsq must be supplied in SCALE and SUMSQ respectively.
52 *> SCALE and SUMSQ are overwritten by scl and ssq respectively.
54 *> The routine makes only one pass through the vector X.
63 *> The number of elements to be used from the vector X.
68 *> X is COMPLEX array, dimension (N)
69 *> The vector x as described above.
70 *> x( i ) = X( 1 + ( i - 1 )*INCX ), 1 <= i <= n.
76 *> The increment between successive values of the vector X.
80 *> \param[in,out] SCALE
83 *> On entry, the value scale in the equation above.
84 *> On exit, SCALE is overwritten with the value scl .
87 *> \param[in,out] SUMSQ
90 *> On entry, the value sumsq in the equation above.
91 *> On exit, SUMSQ is overwritten with the value ssq .
97 *> \author Univ. of Tennessee
98 *> \author Univ. of California Berkeley
99 *> \author Univ. of Colorado Denver
102 *> \date September 2012
104 *> \ingroup complexOTHERauxiliary
106 * =====================================================================
107 SUBROUTINE CLASSQ( N, X, INCX, SCALE, SUMSQ )
109 * -- LAPACK auxiliary routine (version 3.4.2) --
110 * -- LAPACK is a software package provided by Univ. of Tennessee, --
111 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114 * .. Scalar Arguments ..
118 * .. Array Arguments ..
122 * =====================================================================
126 PARAMETER ( ZERO = 0.0E+0 )
128 * .. Local Scalars ..
132 * .. External Functions ..
136 * .. Intrinsic Functions ..
137 INTRINSIC ABS, AIMAG, REAL
139 * .. Executable Statements ..
142 DO 10 IX = 1, 1 + ( N-1 )*INCX, INCX
143 TEMP1 = ABS( REAL( X( IX ) ) )
144 IF( TEMP1.GT.ZERO.OR.SISNAN( TEMP1 ) ) THEN
145 IF( SCALE.LT.TEMP1 ) THEN
146 SUMSQ = 1 + SUMSQ*( SCALE / TEMP1 )**2
149 SUMSQ = SUMSQ + ( TEMP1 / SCALE )**2
152 TEMP1 = ABS( AIMAG( X( IX ) ) )
153 IF( TEMP1.GT.ZERO.OR.SISNAN( TEMP1 ) ) THEN
154 IF( SCALE.LT.TEMP1 .OR. SISNAN( TEMP1 ) ) THEN
155 SUMSQ = 1 + SUMSQ*( SCALE / TEMP1 )**2
158 SUMSQ = SUMSQ + ( TEMP1 / SCALE )**2