LAPACK  3.11.0
LAPACK: Linear Algebra PACKage
classq.f90
1 
2 !
3 ! =========== DOCUMENTATION ===========
4 !
5 ! Online html documentation available at
6 ! http://www.netlib.org/lapack/explore-html/
7 !
17 !
18 ! Definition:
19 ! ===========
20 !
21 ! SUBROUTINE CLASSQ( N, X, INCX, SCALE, SUMSQ )
22 !
23 ! .. Scalar Arguments ..
24 ! INTEGER INCX, N
25 ! REAL SCALE, SUMSQ
26 ! ..
27 ! .. Array Arguments ..
28 ! COMPLEX X( * )
29 ! ..
30 !
31 !
33 ! =============
61 !
62 ! Arguments:
63 ! ==========
64 !
104 !
105 ! Authors:
106 ! ========
107 !
109 !
111 ! ==================
115 !
117 ! =====================
132 !
134 !
135 ! =====================================================================
136 subroutine classq( n, x, incx, scale, sumsq )
137  use la_constants, &
138  only: wp=>sp, zero=>szero, one=>sone, &
139  sbig=>ssbig, ssml=>sssml, tbig=>stbig, tsml=>stsml
140  use la_xisnan
141 !
142 ! -- LAPACK auxiliary routine --
143 ! -- LAPACK is a software package provided by Univ. of Tennessee, --
144 ! -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
145 !
146 ! .. Scalar Arguments ..
147  integer :: incx, n
148  real(wp) :: scale, sumsq
149 ! ..
150 ! .. Array Arguments ..
151  complex(wp) :: x(*)
152 ! ..
153 ! .. Local Scalars ..
154  integer :: i, ix
155  logical :: notbig
156  real(wp) :: abig, amed, asml, ax, ymax, ymin
157 ! ..
158 !
159 ! Quick return if possible
160 !
161  if( la_isnan(scale) .or. la_isnan(sumsq) ) return
162  if( sumsq == zero ) scale = one
163  if( scale == zero ) then
164  scale = one
165  sumsq = zero
166  end if
167  if (n <= 0) then
168  return
169  end if
170 !
171 ! Compute the sum of squares in 3 accumulators:
172 ! abig -- sums of squares scaled down to avoid overflow
173 ! asml -- sums of squares scaled up to avoid underflow
174 ! amed -- sums of squares that do not require scaling
175 ! The thresholds and multipliers are
176 ! tbig -- values bigger than this are scaled down by sbig
177 ! tsml -- values smaller than this are scaled up by ssml
178 !
179  notbig = .true.
180  asml = zero
181  amed = zero
182  abig = zero
183  ix = 1
184  if( incx < 0 ) ix = 1 - (n-1)*incx
185  do i = 1, n
186  ax = abs(real(x(ix)))
187  if (ax > tbig) then
188  abig = abig + (ax*sbig)**2
189  notbig = .false.
190  else if (ax < tsml) then
191  if (notbig) asml = asml + (ax*ssml)**2
192  else
193  amed = amed + ax**2
194  end if
195  ax = abs(aimag(x(ix)))
196  if (ax > tbig) then
197  abig = abig + (ax*sbig)**2
198  notbig = .false.
199  else if (ax < tsml) then
200  if (notbig) asml = asml + (ax*ssml)**2
201  else
202  amed = amed + ax**2
203  end if
204  ix = ix + incx
205  end do
206 !
207 ! Put the existing sum of squares into one of the accumulators
208 !
209  if( sumsq > zero ) then
210  ax = scale*sqrt( sumsq )
211  if (ax > tbig) then
212 ! We assume scale >= sqrt( TINY*EPS ) / sbig
213  abig = abig + (scale*sbig)**2 * sumsq
214  else if (ax < tsml) then
215 ! We assume scale <= sqrt( HUGE ) / ssml
216  if (notbig) asml = asml + (scale*ssml)**2 * sumsq
217  else
218  amed = amed + scale**2 * sumsq
219  end if
220  end if
221 !
222 ! Combine abig and amed or amed and asml if more than one
223 ! accumulator was used.
224 !
225  if (abig > zero) then
226 !
227 ! Combine abig and amed if abig > 0.
228 !
229  if (amed > zero .or. la_isnan(amed)) then
230  abig = abig + (amed*sbig)*sbig
231  end if
232  scale = one / sbig
233  sumsq = abig
234  else if (asml > zero) then
235 !
236 ! Combine amed and asml if asml > 0.
237 !
238  if (amed > zero .or. la_isnan(amed)) then
239  amed = sqrt(amed)
240  asml = sqrt(asml) / ssml
241  if (asml > amed) then
242  ymin = amed
243  ymax = asml
244  else
245  ymin = asml
246  ymax = amed
247  end if
248  scale = one
249  sumsq = ymax**2*( one + (ymin/ymax)**2 )
250  else
251  scale = one / ssml
252  sumsq = asml
253  end if
254  else
255 !
256 ! Otherwise all values are mid-range or zero
257 !
258  scale = one
259  sumsq = amed
260  end if
261  return
262 end subroutine
LA_CONSTANTS is a module for the scaling constants for the compiled Fortran single and double precisi...