You can not select more than 25 topics Topics must start with a chinese character,a letter or number, can include dashes ('-') and can be up to 35 characters long.

zlassq.f90 7.3 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261
  1. !> \brief \b ZLASSQ updates a sum of squares represented in scaled form.
  2. !
  3. ! =========== DOCUMENTATION ===========
  4. !
  5. ! Online html documentation available at
  6. ! http://www.netlib.org/lapack/explore-html/
  7. !
  8. !> \htmlonly
  9. !> Download ZLASSQ + dependencies
  10. !> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlassq.f90">
  11. !> [TGZ]</a>
  12. !> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlassq.f90">
  13. !> [ZIP]</a>
  14. !> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlassq.f90">
  15. !> [TXT]</a>
  16. !> \endhtmlonly
  17. !
  18. ! Definition:
  19. ! ===========
  20. !
  21. ! SUBROUTINE ZLASSQ( N, X, INCX, SCALE, SUMSQ )
  22. !
  23. ! .. Scalar Arguments ..
  24. ! INTEGER INCX, N
  25. ! DOUBLE PRECISION SCALE, SUMSQ
  26. ! ..
  27. ! .. Array Arguments ..
  28. ! DOUBLE COMPLEX X( * )
  29. ! ..
  30. !
  31. !
  32. !> \par Purpose:
  33. ! =============
  34. !>
  35. !> \verbatim
  36. !>
  37. !> ZLASSQ returns the values scale_out and sumsq_out such that
  38. !>
  39. !> (scale_out**2)*sumsq_out = x( 1 )**2 +...+ x( n )**2 + (scale**2)*sumsq,
  40. !>
  41. !> where x( i ) = X( 1 + ( i - 1 )*INCX ). The value of sumsq is
  42. !> assumed to be non-negative.
  43. !>
  44. !> scale and sumsq must be supplied in SCALE and SUMSQ and
  45. !> scale_out and sumsq_out are overwritten on SCALE and SUMSQ respectively.
  46. !>
  47. !> \endverbatim
  48. !
  49. ! Arguments:
  50. ! ==========
  51. !
  52. !> \param[in] N
  53. !> \verbatim
  54. !> N is INTEGER
  55. !> The number of elements to be used from the vector x.
  56. !> \endverbatim
  57. !>
  58. !> \param[in] X
  59. !> \verbatim
  60. !> X is DOUBLE COMPLEX array, dimension (1+(N-1)*abs(INCX))
  61. !> The vector for which a scaled sum of squares is computed.
  62. !> x( i ) = X( 1 + ( i - 1 )*INCX ), 1 <= i <= n.
  63. !> \endverbatim
  64. !>
  65. !> \param[in] INCX
  66. !> \verbatim
  67. !> INCX is INTEGER
  68. !> The increment between successive values of the vector x.
  69. !> If INCX > 0, X(1+(i-1)*INCX) = x(i) for 1 <= i <= n
  70. !> If INCX < 0, X(1-(n-i)*INCX) = x(i) for 1 <= i <= n
  71. !> If INCX = 0, x isn't a vector so there is no need to call
  72. !> this subroutine. If you call it anyway, it will count x(1)
  73. !> in the vector norm N times.
  74. !> \endverbatim
  75. !>
  76. !> \param[in,out] SCALE
  77. !> \verbatim
  78. !> SCALE is DOUBLE PRECISION
  79. !> On entry, the value scale in the equation above.
  80. !> On exit, SCALE is overwritten by scale_out, the scaling factor
  81. !> for the sum of squares.
  82. !> \endverbatim
  83. !>
  84. !> \param[in,out] SUMSQ
  85. !> \verbatim
  86. !> SUMSQ is DOUBLE PRECISION
  87. !> On entry, the value sumsq in the equation above.
  88. !> On exit, SUMSQ is overwritten by sumsq_out, the basic sum of
  89. !> squares from which scale_out has been factored out.
  90. !> \endverbatim
  91. !
  92. ! Authors:
  93. ! ========
  94. !
  95. !> \author Edward Anderson, Lockheed Martin
  96. !
  97. !> \par Contributors:
  98. ! ==================
  99. !>
  100. !> Weslley Pereira, University of Colorado Denver, USA
  101. !> Nick Papior, Technical University of Denmark, DK
  102. !
  103. !> \par Further Details:
  104. ! =====================
  105. !>
  106. !> \verbatim
  107. !>
  108. !> Anderson E. (2017)
  109. !> Algorithm 978: Safe Scaling in the Level 1 BLAS
  110. !> ACM Trans Math Softw 44:1--28
  111. !> https://doi.org/10.1145/3061665
  112. !>
  113. !> Blue, James L. (1978)
  114. !> A Portable Fortran Program to Find the Euclidean Norm of a Vector
  115. !> ACM Trans Math Softw 4:15--23
  116. !> https://doi.org/10.1145/355769.355771
  117. !>
  118. !> \endverbatim
  119. !
  120. !> \ingroup lassq
  121. !
  122. ! =====================================================================
  123. subroutine ZLASSQ( n, x, incx, scale, sumsq )
  124. use LA_CONSTANTS, &
  125. only: wp=>dp, zero=>dzero, one=>done, &
  126. sbig=>dsbig, ssml=>dssml, tbig=>dtbig, tsml=>dtsml
  127. use LA_XISNAN
  128. !
  129. ! -- LAPACK auxiliary routine --
  130. ! -- LAPACK is a software package provided by Univ. of Tennessee, --
  131. ! -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  132. !
  133. ! .. Scalar Arguments ..
  134. integer :: incx, n
  135. real(wp) :: scale, sumsq
  136. ! ..
  137. ! .. Array Arguments ..
  138. complex(wp) :: x(*)
  139. ! ..
  140. ! .. Local Scalars ..
  141. integer :: i, ix
  142. logical :: notbig
  143. real(wp) :: abig, amed, asml, ax, ymax, ymin
  144. ! ..
  145. !
  146. ! Quick return if possible
  147. !
  148. if( LA_ISNAN(scale) .or. LA_ISNAN(sumsq) ) return
  149. if( sumsq == zero ) scale = one
  150. if( scale == zero ) then
  151. scale = one
  152. sumsq = zero
  153. end if
  154. if (n <= 0) then
  155. return
  156. end if
  157. !
  158. ! Compute the sum of squares in 3 accumulators:
  159. ! abig -- sums of squares scaled down to avoid overflow
  160. ! asml -- sums of squares scaled up to avoid underflow
  161. ! amed -- sums of squares that do not require scaling
  162. ! The thresholds and multipliers are
  163. ! tbig -- values bigger than this are scaled down by sbig
  164. ! tsml -- values smaller than this are scaled up by ssml
  165. !
  166. notbig = .true.
  167. asml = zero
  168. amed = zero
  169. abig = zero
  170. ix = 1
  171. if( incx < 0 ) ix = 1 - (n-1)*incx
  172. do i = 1, n
  173. ax = abs(real(x(ix)))
  174. if (ax > tbig) then
  175. abig = abig + (ax*sbig)**2
  176. notbig = .false.
  177. else if (ax < tsml) then
  178. if (notbig) asml = asml + (ax*ssml)**2
  179. else
  180. amed = amed + ax**2
  181. end if
  182. ax = abs(aimag(x(ix)))
  183. if (ax > tbig) then
  184. abig = abig + (ax*sbig)**2
  185. notbig = .false.
  186. else if (ax < tsml) then
  187. if (notbig) asml = asml + (ax*ssml)**2
  188. else
  189. amed = amed + ax**2
  190. end if
  191. ix = ix + incx
  192. end do
  193. !
  194. ! Put the existing sum of squares into one of the accumulators
  195. !
  196. if( sumsq > zero ) then
  197. ax = scale*sqrt( sumsq )
  198. if (ax > tbig) then
  199. if (scale > one) then
  200. scale = scale * sbig
  201. abig = abig + scale * (scale * sumsq)
  202. else
  203. ! sumsq > tbig^2 => (sbig * (sbig * sumsq)) is representable
  204. abig = abig + scale * (scale * (sbig * (sbig * sumsq)))
  205. end if
  206. else if (ax < tsml) then
  207. if (notbig) then
  208. if (scale < one) then
  209. scale = scale * ssml
  210. asml = asml + scale * (scale * sumsq)
  211. else
  212. ! sumsq < tsml^2 => (ssml * (ssml * sumsq)) is representable
  213. asml = asml + scale * (scale * (ssml * (ssml * sumsq)))
  214. end if
  215. end if
  216. else
  217. amed = amed + scale * (scale * sumsq)
  218. end if
  219. end if
  220. !
  221. ! Combine abig and amed or amed and asml if more than one
  222. ! accumulator was used.
  223. !
  224. if (abig > zero) then
  225. !
  226. ! Combine abig and amed if abig > 0.
  227. !
  228. if (amed > zero .or. LA_ISNAN(amed)) then
  229. abig = abig + (amed*sbig)*sbig
  230. end if
  231. scale = one / sbig
  232. sumsq = abig
  233. else if (asml > zero) then
  234. !
  235. ! Combine amed and asml if asml > 0.
  236. !
  237. if (amed > zero .or. LA_ISNAN(amed)) then
  238. amed = sqrt(amed)
  239. asml = sqrt(asml) / ssml
  240. if (asml > amed) then
  241. ymin = amed
  242. ymax = asml
  243. else
  244. ymin = asml
  245. ymax = amed
  246. end if
  247. scale = one
  248. sumsq = ymax**2*( one + (ymin/ymax)**2 )
  249. else
  250. scale = one / ssml
  251. sumsq = asml
  252. end if
  253. else
  254. !
  255. ! Otherwise all values are mid-range or zero
  256. !
  257. scale = one
  258. sumsq = amed
  259. end if
  260. return
  261. end subroutine