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.

chpr2f.f 8.5 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251
  1. SUBROUTINE CHPR2F( UPLO, N, ALPHA, X, INCX, Y, INCY, AP )
  2. * .. Scalar Arguments ..
  3. COMPLEX ALPHA
  4. INTEGER INCX, INCY, N
  5. CHARACTER*1 UPLO
  6. * .. Array Arguments ..
  7. COMPLEX AP( * ), X( * ), Y( * )
  8. * ..
  9. *
  10. * Purpose
  11. * =======
  12. *
  13. * CHPR2 performs the hermitian rank 2 operation
  14. *
  15. * A := alpha*x*conjg( y' ) + conjg( alpha )*y*conjg( x' ) + A,
  16. *
  17. * where alpha is a scalar, x and y are n element vectors and A is an
  18. * n by n hermitian matrix, supplied in packed form.
  19. *
  20. * Parameters
  21. * ==========
  22. *
  23. * UPLO - CHARACTER*1.
  24. * On entry, UPLO specifies whether the upper or lower
  25. * triangular part of the matrix A is supplied in the packed
  26. * array AP as follows:
  27. *
  28. * UPLO = 'U' or 'u' The upper triangular part of A is
  29. * supplied in AP.
  30. *
  31. * UPLO = 'L' or 'l' The lower triangular part of A is
  32. * supplied in AP.
  33. *
  34. * Unchanged on exit.
  35. *
  36. * N - INTEGER.
  37. * On entry, N specifies the order of the matrix A.
  38. * N must be at least zero.
  39. * Unchanged on exit.
  40. *
  41. * ALPHA - COMPLEX .
  42. * On entry, ALPHA specifies the scalar alpha.
  43. * Unchanged on exit.
  44. *
  45. * X - COMPLEX array of dimension at least
  46. * ( 1 + ( n - 1 )*abs( INCX ) ).
  47. * Before entry, the incremented array X must contain the n
  48. * element vector x.
  49. * Unchanged on exit.
  50. *
  51. * INCX - INTEGER.
  52. * On entry, INCX specifies the increment for the elements of
  53. * X. INCX must not be zero.
  54. * Unchanged on exit.
  55. *
  56. * Y - COMPLEX array of dimension at least
  57. * ( 1 + ( n - 1 )*abs( INCY ) ).
  58. * Before entry, the incremented array Y must contain the n
  59. * element vector y.
  60. * Unchanged on exit.
  61. *
  62. * INCY - INTEGER.
  63. * On entry, INCY specifies the increment for the elements of
  64. * Y. INCY must not be zero.
  65. * Unchanged on exit.
  66. *
  67. * AP - COMPLEX array of DIMENSION at least
  68. * ( ( n*( n + 1 ) )/2 ).
  69. * Before entry with UPLO = 'U' or 'u', the array AP must
  70. * contain the upper triangular part of the hermitian matrix
  71. * packed sequentially, column by column, so that AP( 1 )
  72. * contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
  73. * and a( 2, 2 ) respectively, and so on. On exit, the array
  74. * AP is overwritten by the upper triangular part of the
  75. * updated matrix.
  76. * Before entry with UPLO = 'L' or 'l', the array AP must
  77. * contain the lower triangular part of the hermitian matrix
  78. * packed sequentially, column by column, so that AP( 1 )
  79. * contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
  80. * and a( 3, 1 ) respectively, and so on. On exit, the array
  81. * AP is overwritten by the lower triangular part of the
  82. * updated matrix.
  83. * Note that the imaginary parts of the diagonal elements need
  84. * not be set, they are assumed to be zero, and on exit they
  85. * are set to zero.
  86. *
  87. *
  88. * Level 2 Blas routine.
  89. *
  90. * -- Written on 22-October-1986.
  91. * Jack Dongarra, Argonne National Lab.
  92. * Jeremy Du Croz, Nag Central Office.
  93. * Sven Hammarling, Nag Central Office.
  94. * Richard Hanson, Sandia National Labs.
  95. *
  96. *
  97. * .. Parameters ..
  98. COMPLEX ZERO
  99. PARAMETER ( ZERO = ( 0.0E+0, 0.0E+0 ) )
  100. * .. Local Scalars ..
  101. COMPLEX TEMP1, TEMP2
  102. INTEGER I, INFO, IX, IY, J, JX, JY, K, KK, KX, KY
  103. * .. External Functions ..
  104. LOGICAL LSAME
  105. EXTERNAL LSAME
  106. * .. External Subroutines ..
  107. EXTERNAL XERBLA
  108. * .. Intrinsic Functions ..
  109. INTRINSIC CONJG, REAL
  110. * ..
  111. * .. Executable Statements ..
  112. *
  113. * Test the input parameters.
  114. *
  115. INFO = 0
  116. IF ( .NOT.LSAME( UPLO, 'U' ).AND.
  117. $ .NOT.LSAME( UPLO, 'L' ) )THEN
  118. INFO = 1
  119. ELSE IF( N.LT.0 )THEN
  120. INFO = 2
  121. ELSE IF( INCX.EQ.0 )THEN
  122. INFO = 5
  123. ELSE IF( INCY.EQ.0 )THEN
  124. INFO = 7
  125. END IF
  126. IF( INFO.NE.0 )THEN
  127. CALL XERBLA( 'CHPR2 ', INFO )
  128. RETURN
  129. END IF
  130. *
  131. * Quick return if possible.
  132. *
  133. IF( ( N.EQ.0 ).OR.( ALPHA.EQ.ZERO ) )
  134. $ RETURN
  135. *
  136. * Set up the start points in X and Y if the increments are not both
  137. * unity.
  138. *
  139. IF( ( INCX.NE.1 ).OR.( INCY.NE.1 ) )THEN
  140. IF( INCX.GT.0 )THEN
  141. KX = 1
  142. ELSE
  143. KX = 1 - ( N - 1 )*INCX
  144. END IF
  145. IF( INCY.GT.0 )THEN
  146. KY = 1
  147. ELSE
  148. KY = 1 - ( N - 1 )*INCY
  149. END IF
  150. JX = KX
  151. JY = KY
  152. END IF
  153. *
  154. * Start the operations. In this version the elements of the array AP
  155. * are accessed sequentially with one pass through AP.
  156. *
  157. KK = 1
  158. IF( LSAME( UPLO, 'U' ) )THEN
  159. *
  160. * Form A when upper triangle is stored in AP.
  161. *
  162. IF( ( INCX.EQ.1 ).AND.( INCY.EQ.1 ) )THEN
  163. DO 20, J = 1, N
  164. IF( ( X( J ).NE.ZERO ).OR.( Y( J ).NE.ZERO ) )THEN
  165. TEMP1 = ALPHA*CONJG( Y( J ) )
  166. TEMP2 = CONJG( ALPHA*X( J ) )
  167. K = KK
  168. DO 10, I = 1, J - 1
  169. AP( K ) = AP( K ) + X( I )*TEMP1 + Y( I )*TEMP2
  170. K = K + 1
  171. 10 CONTINUE
  172. AP( KK + J - 1 ) = REAL( AP( KK + J - 1 ) ) +
  173. $ REAL( X( J )*TEMP1 + Y( J )*TEMP2 )
  174. ELSE
  175. AP( KK + J - 1 ) = REAL( AP( KK + J - 1 ) )
  176. END IF
  177. KK = KK + J
  178. 20 CONTINUE
  179. ELSE
  180. DO 40, J = 1, N
  181. IF( ( X( JX ).NE.ZERO ).OR.( Y( JY ).NE.ZERO ) )THEN
  182. TEMP1 = ALPHA*CONJG( Y( JY ) )
  183. TEMP2 = CONJG( ALPHA*X( JX ) )
  184. IX = KX
  185. IY = KY
  186. DO 30, K = KK, KK + J - 2
  187. AP( K ) = AP( K ) + X( IX )*TEMP1 + Y( IY )*TEMP2
  188. IX = IX + INCX
  189. IY = IY + INCY
  190. 30 CONTINUE
  191. AP( KK + J - 1 ) = REAL( AP( KK + J - 1 ) ) +
  192. $ REAL( X( JX )*TEMP1 +
  193. $ Y( JY )*TEMP2 )
  194. ELSE
  195. AP( KK + J - 1 ) = REAL( AP( KK + J - 1 ) )
  196. END IF
  197. JX = JX + INCX
  198. JY = JY + INCY
  199. KK = KK + J
  200. 40 CONTINUE
  201. END IF
  202. ELSE
  203. *
  204. * Form A when lower triangle is stored in AP.
  205. *
  206. IF( ( INCX.EQ.1 ).AND.( INCY.EQ.1 ) )THEN
  207. DO 60, J = 1, N
  208. IF( ( X( J ).NE.ZERO ).OR.( Y( J ).NE.ZERO ) )THEN
  209. TEMP1 = ALPHA*CONJG( Y( J ) )
  210. TEMP2 = CONJG( ALPHA*X( J ) )
  211. AP( KK ) = REAL( AP( KK ) ) +
  212. $ REAL( X( J )*TEMP1 + Y( J )*TEMP2 )
  213. K = KK + 1
  214. DO 50, I = J + 1, N
  215. AP( K ) = AP( K ) + X( I )*TEMP1 + Y( I )*TEMP2
  216. K = K + 1
  217. 50 CONTINUE
  218. ELSE
  219. AP( KK ) = REAL( AP( KK ) )
  220. END IF
  221. KK = KK + N - J + 1
  222. 60 CONTINUE
  223. ELSE
  224. DO 80, J = 1, N
  225. IF( ( X( JX ).NE.ZERO ).OR.( Y( JY ).NE.ZERO ) )THEN
  226. TEMP1 = ALPHA*CONJG( Y( JY ) )
  227. TEMP2 = CONJG( ALPHA*X( JX ) )
  228. AP( KK ) = REAL( AP( KK ) ) +
  229. $ REAL( X( JX )*TEMP1 + Y( JY )*TEMP2 )
  230. IX = JX
  231. IY = JY
  232. DO 70, K = KK + 1, KK + N - J
  233. IX = IX + INCX
  234. IY = IY + INCY
  235. AP( K ) = AP( K ) + X( IX )*TEMP1 + Y( IY )*TEMP2
  236. 70 CONTINUE
  237. ELSE
  238. AP( KK ) = REAL( AP( KK ) )
  239. END IF
  240. JX = JX + INCX
  241. JY = JY + INCY
  242. KK = KK + N - J + 1
  243. 80 CONTINUE
  244. END IF
  245. END IF
  246. *
  247. RETURN
  248. *
  249. * End of CHPR2 .
  250. *
  251. END