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.

zunhr_col01.f 11 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390
  1. *> \brief \b ZUNHR_COL01
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. * Definition:
  9. * ===========
  10. *
  11. * SUBROUTINE ZUNHR_COL01( M, N, MB1, NB1, NB2, RESULT )
  12. *
  13. * .. Scalar Arguments ..
  14. * INTEGER M, N, MB1, NB1, NB2
  15. * .. Return values ..
  16. * DOUBLE PRECISION RESULT(6)
  17. *
  18. *
  19. *> \par Purpose:
  20. * =============
  21. *>
  22. *> \verbatim
  23. *>
  24. *> ZUNHR_COL01 tests ZUNHR_COL using ZLATSQR, ZGEMQRT and ZUNGTSQR.
  25. *> Therefore, ZLATSQR (part of ZGEQR), ZGEMQRT (part ZGEMQR), ZUNGTSQR
  26. *> have to be tested before this test.
  27. *>
  28. *> \endverbatim
  29. *
  30. * Arguments:
  31. * ==========
  32. *
  33. *> \param[in] M
  34. *> \verbatim
  35. *> M is INTEGER
  36. *> Number of rows in test matrix.
  37. *> \endverbatim
  38. *> \param[in] N
  39. *> \verbatim
  40. *> N is INTEGER
  41. *> Number of columns in test matrix.
  42. *> \endverbatim
  43. *> \param[in] MB1
  44. *> \verbatim
  45. *> MB1 is INTEGER
  46. *> Number of row in row block in an input test matrix.
  47. *> \endverbatim
  48. *>
  49. *> \param[in] NB1
  50. *> \verbatim
  51. *> NB1 is INTEGER
  52. *> Number of columns in column block an input test matrix.
  53. *> \endverbatim
  54. *>
  55. *> \param[in] NB2
  56. *> \verbatim
  57. *> NB2 is INTEGER
  58. *> Number of columns in column block in an output test matrix.
  59. *> \endverbatim
  60. *>
  61. *> \param[out] RESULT
  62. *> \verbatim
  63. *> RESULT is DOUBLE PRECISION array, dimension (6)
  64. *> Results of each of the six tests below.
  65. *> ( C is a M-by-N random matrix, D is a N-by-M random matrix )
  66. *>
  67. *> RESULT(1) = | A - Q * R | / (eps * m * |A|)
  68. *> RESULT(2) = | I - (Q**H) * Q | / (eps * m )
  69. *> RESULT(3) = | Q * C - Q * C | / (eps * m * |C|)
  70. *> RESULT(4) = | (Q**H) * C - (Q**H) * C | / (eps * m * |C|)
  71. *> RESULT(5) = | (D * Q) - D * Q | / (eps * m * |D|)
  72. *> RESULT(6) = | D * (Q**H) - D * (Q**H) | / (eps * m * |D|)
  73. *> \endverbatim
  74. *
  75. * Authors:
  76. * ========
  77. *
  78. *> \author Univ. of Tennessee
  79. *> \author Univ. of California Berkeley
  80. *> \author Univ. of Colorado Denver
  81. *> \author NAG Ltd.
  82. *
  83. *> \date November 2019
  84. *
  85. *> \ingroup complex16_lin
  86. *
  87. * =====================================================================
  88. SUBROUTINE ZUNHR_COL01( M, N, MB1, NB1, NB2, RESULT )
  89. IMPLICIT NONE
  90. *
  91. * -- LAPACK test routine (version 3.9.0) --
  92. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  93. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  94. * November 2019
  95. *
  96. * .. Scalar Arguments ..
  97. INTEGER M, N, MB1, NB1, NB2
  98. * .. Return values ..
  99. DOUBLE PRECISION RESULT(6)
  100. *
  101. * =====================================================================
  102. *
  103. * ..
  104. * .. Local allocatable arrays
  105. COMPLEX*16, ALLOCATABLE :: A(:,:), AF(:,:), Q(:,:), R(:,:),
  106. $ WORK( : ), T1(:,:), T2(:,:), DIAG(:),
  107. $ C(:,:), CF(:,:), D(:,:), DF(:,:)
  108. DOUBLE PRECISION, ALLOCATABLE :: RWORK(:)
  109. *
  110. * .. Parameters ..
  111. DOUBLE PRECISION ZERO
  112. PARAMETER ( ZERO = 0.0D+0 )
  113. COMPLEX*16 CONE, CZERO
  114. PARAMETER ( CONE = ( 1.0D+0, 0.0D+0 ),
  115. $ CZERO = ( 0.0D+0, 0.0D+0 ) )
  116. * ..
  117. * .. Local Scalars ..
  118. LOGICAL TESTZEROS
  119. INTEGER INFO, I, J, K, L, LWORK, NB1_UB, NB2_UB, NRB
  120. DOUBLE PRECISION ANORM, EPS, RESID, CNORM, DNORM
  121. * ..
  122. * .. Local Arrays ..
  123. INTEGER ISEED( 4 )
  124. COMPLEX*16 WORKQUERY( 1 )
  125. * ..
  126. * .. External Functions ..
  127. DOUBLE PRECISION DLAMCH, ZLANGE, ZLANSY
  128. EXTERNAL DLAMCH, ZLANGE, ZLANSY
  129. * ..
  130. * .. External Subroutines ..
  131. EXTERNAL ZLACPY, ZLARNV, ZLASET, ZLATSQR, ZUNHR_COL,
  132. $ ZUNGTSQR, ZSCAL, ZGEMM, ZGEMQRT, ZHERK
  133. * ..
  134. * .. Intrinsic Functions ..
  135. INTRINSIC CEILING, DBLE, MAX, MIN
  136. * ..
  137. * .. Scalars in Common ..
  138. CHARACTER(LEN=32) SRNAMT
  139. * ..
  140. * .. Common blocks ..
  141. COMMON / SRMNAMC / SRNAMT
  142. * ..
  143. * .. Data statements ..
  144. DATA ISEED / 1988, 1989, 1990, 1991 /
  145. *
  146. * TEST MATRICES WITH HALF OF MATRIX BEING ZEROS
  147. *
  148. TESTZEROS = .FALSE.
  149. *
  150. EPS = DLAMCH( 'Epsilon' )
  151. K = MIN( M, N )
  152. L = MAX( M, N, 1)
  153. *
  154. * Dynamically allocate local arrays
  155. *
  156. ALLOCATE ( A(M,N), AF(M,N), Q(L,L), R(M,L), RWORK(L),
  157. $ C(M,N), CF(M,N),
  158. $ D(N,M), DF(N,M) )
  159. *
  160. * Put random numbers into A and copy to AF
  161. *
  162. DO J = 1, N
  163. CALL ZLARNV( 2, ISEED, M, A( 1, J ) )
  164. END DO
  165. IF( TESTZEROS ) THEN
  166. IF( M.GE.4 ) THEN
  167. DO J = 1, N
  168. CALL ZLARNV( 2, ISEED, M/2, A( M/4, J ) )
  169. END DO
  170. END IF
  171. END IF
  172. CALL ZLACPY( 'Full', M, N, A, M, AF, M )
  173. *
  174. * Number of row blocks in ZLATSQR
  175. *
  176. NRB = MAX( 1, CEILING( DBLE( M - N ) / DBLE( MB1 - N ) ) )
  177. *
  178. ALLOCATE ( T1( NB1, N * NRB ) )
  179. ALLOCATE ( T2( NB2, N ) )
  180. ALLOCATE ( DIAG( N ) )
  181. *
  182. * Begin determine LWORK for the array WORK and allocate memory.
  183. *
  184. * ZLATSQR requires NB1 to be bounded by N.
  185. *
  186. NB1_UB = MIN( NB1, N)
  187. *
  188. * ZGEMQRT requires NB2 to be bounded by N.
  189. *
  190. NB2_UB = MIN( NB2, N)
  191. *
  192. CALL ZLATSQR( M, N, MB1, NB1_UB, AF, M, T1, NB1,
  193. $ WORKQUERY, -1, INFO )
  194. LWORK = INT( WORKQUERY( 1 ) )
  195. CALL ZUNGTSQR( M, N, MB1, NB1, AF, M, T1, NB1, WORKQUERY, -1,
  196. $ INFO )
  197. LWORK = MAX( LWORK, INT( WORKQUERY( 1 ) ) )
  198. *
  199. * In ZGEMQRT, WORK is N*NB2_UB if SIDE = 'L',
  200. * or M*NB2_UB if SIDE = 'R'.
  201. *
  202. LWORK = MAX( LWORK, NB2_UB * N, NB2_UB * M )
  203. *
  204. ALLOCATE ( WORK( LWORK ) )
  205. *
  206. * End allocate memory for WORK.
  207. *
  208. *
  209. * Begin Householder reconstruction routines
  210. *
  211. * Factor the matrix A in the array AF.
  212. *
  213. SRNAMT = 'ZLATSQR'
  214. CALL ZLATSQR( M, N, MB1, NB1_UB, AF, M, T1, NB1, WORK, LWORK,
  215. $ INFO )
  216. *
  217. * Copy the factor R into the array R.
  218. *
  219. SRNAMT = 'ZLACPY'
  220. CALL ZLACPY( 'U', M, N, AF, M, R, M )
  221. *
  222. * Reconstruct the orthogonal matrix Q.
  223. *
  224. SRNAMT = 'ZUNGTSQR'
  225. CALL ZUNGTSQR( M, N, MB1, NB1, AF, M, T1, NB1, WORK, LWORK,
  226. $ INFO )
  227. *
  228. * Perform the Householder reconstruction, the result is stored
  229. * the arrays AF and T2.
  230. *
  231. SRNAMT = 'ZUNHR_COL'
  232. CALL ZUNHR_COL( M, N, NB2, AF, M, T2, NB2, DIAG, INFO )
  233. *
  234. * Compute the factor R_hr corresponding to the Householder
  235. * reconstructed Q_hr and place it in the upper triangle of AF to
  236. * match the Q storage format in ZGEQRT. R_hr = R_tsqr * S,
  237. * this means changing the sign of I-th row of the matrix R_tsqr
  238. * according to sign of of I-th diagonal element DIAG(I) of the
  239. * matrix S.
  240. *
  241. SRNAMT = 'ZLACPY'
  242. CALL ZLACPY( 'U', M, N, R, M, AF, M )
  243. *
  244. DO I = 1, N
  245. IF( DIAG( I ).EQ.-CONE ) THEN
  246. CALL ZSCAL( N+1-I, -CONE, AF( I, I ), M )
  247. END IF
  248. END DO
  249. *
  250. * End Householder reconstruction routines.
  251. *
  252. *
  253. * Generate the m-by-m matrix Q
  254. *
  255. CALL ZLASET( 'Full', M, M, CZERO, CONE, Q, M )
  256. *
  257. SRNAMT = 'ZGEMQRT'
  258. CALL ZGEMQRT( 'L', 'N', M, M, K, NB2_UB, AF, M, T2, NB2, Q, M,
  259. $ WORK, INFO )
  260. *
  261. * Copy R
  262. *
  263. CALL ZLASET( 'Full', M, N, CZERO, CZERO, R, M )
  264. *
  265. CALL ZLACPY( 'Upper', M, N, AF, M, R, M )
  266. *
  267. * TEST 1
  268. * Compute |R - (Q**H)*A| / ( eps * m * |A| ) and store in RESULT(1)
  269. *
  270. CALL ZGEMM( 'C', 'N', M, N, M, -CONE, Q, M, A, M, CONE, R, M )
  271. *
  272. ANORM = ZLANGE( '1', M, N, A, M, RWORK )
  273. RESID = ZLANGE( '1', M, N, R, M, RWORK )
  274. IF( ANORM.GT.ZERO ) THEN
  275. RESULT( 1 ) = RESID / ( EPS * MAX( 1, M ) * ANORM )
  276. ELSE
  277. RESULT( 1 ) = ZERO
  278. END IF
  279. *
  280. * TEST 2
  281. * Compute |I - (Q**H)*Q| / ( eps * m ) and store in RESULT(2)
  282. *
  283. CALL ZLASET( 'Full', M, M, CZERO, CONE, R, M )
  284. CALL ZHERK( 'U', 'C', M, M, -CONE, Q, M, CONE, R, M )
  285. RESID = ZLANSY( '1', 'Upper', M, R, M, RWORK )
  286. RESULT( 2 ) = RESID / ( EPS * MAX( 1, M ) )
  287. *
  288. * Generate random m-by-n matrix C
  289. *
  290. DO J = 1, N
  291. CALL ZLARNV( 2, ISEED, M, C( 1, J ) )
  292. END DO
  293. CNORM = ZLANGE( '1', M, N, C, M, RWORK )
  294. CALL ZLACPY( 'Full', M, N, C, M, CF, M )
  295. *
  296. * Apply Q to C as Q*C = CF
  297. *
  298. SRNAMT = 'ZGEMQRT'
  299. CALL ZGEMQRT( 'L', 'N', M, N, K, NB2_UB, AF, M, T2, NB2, CF, M,
  300. $ WORK, INFO )
  301. *
  302. * TEST 3
  303. * Compute |CF - Q*C| / ( eps * m * |C| )
  304. *
  305. CALL ZGEMM( 'N', 'N', M, N, M, -CONE, Q, M, C, M, CONE, CF, M )
  306. RESID = ZLANGE( '1', M, N, CF, M, RWORK )
  307. IF( CNORM.GT.ZERO ) THEN
  308. RESULT( 3 ) = RESID / ( EPS * MAX( 1, M ) * CNORM )
  309. ELSE
  310. RESULT( 3 ) = ZERO
  311. END IF
  312. *
  313. * Copy C into CF again
  314. *
  315. CALL ZLACPY( 'Full', M, N, C, M, CF, M )
  316. *
  317. * Apply Q to C as (Q**H)*C = CF
  318. *
  319. SRNAMT = 'ZGEMQRT'
  320. CALL ZGEMQRT( 'L', 'C', M, N, K, NB2_UB, AF, M, T2, NB2, CF, M,
  321. $ WORK, INFO )
  322. *
  323. * TEST 4
  324. * Compute |CF - (Q**H)*C| / ( eps * m * |C|)
  325. *
  326. CALL ZGEMM( 'C', 'N', M, N, M, -CONE, Q, M, C, M, CONE, CF, M )
  327. RESID = ZLANGE( '1', M, N, CF, M, RWORK )
  328. IF( CNORM.GT.ZERO ) THEN
  329. RESULT( 4 ) = RESID / ( EPS * MAX( 1, M ) * CNORM )
  330. ELSE
  331. RESULT( 4 ) = ZERO
  332. END IF
  333. *
  334. * Generate random n-by-m matrix D and a copy DF
  335. *
  336. DO J = 1, M
  337. CALL ZLARNV( 2, ISEED, N, D( 1, J ) )
  338. END DO
  339. DNORM = ZLANGE( '1', N, M, D, N, RWORK )
  340. CALL ZLACPY( 'Full', N, M, D, N, DF, N )
  341. *
  342. * Apply Q to D as D*Q = DF
  343. *
  344. SRNAMT = 'ZGEMQRT'
  345. CALL ZGEMQRT( 'R', 'N', N, M, K, NB2_UB, AF, M, T2, NB2, DF, N,
  346. $ WORK, INFO )
  347. *
  348. * TEST 5
  349. * Compute |DF - D*Q| / ( eps * m * |D| )
  350. *
  351. CALL ZGEMM( 'N', 'N', N, M, M, -CONE, D, N, Q, M, CONE, DF, N )
  352. RESID = ZLANGE( '1', N, M, DF, N, RWORK )
  353. IF( DNORM.GT.ZERO ) THEN
  354. RESULT( 5 ) = RESID / ( EPS * MAX( 1, M ) * DNORM )
  355. ELSE
  356. RESULT( 5 ) = ZERO
  357. END IF
  358. *
  359. * Copy D into DF again
  360. *
  361. CALL ZLACPY( 'Full', N, M, D, N, DF, N )
  362. *
  363. * Apply Q to D as D*QT = DF
  364. *
  365. SRNAMT = 'ZGEMQRT'
  366. CALL ZGEMQRT( 'R', 'C', N, M, K, NB2_UB, AF, M, T2, NB2, DF, N,
  367. $ WORK, INFO )
  368. *
  369. * TEST 6
  370. * Compute |DF - D*(Q**H)| / ( eps * m * |D| )
  371. *
  372. CALL ZGEMM( 'N', 'C', N, M, M, -CONE, D, N, Q, M, CONE, DF, N )
  373. RESID = ZLANGE( '1', N, M, DF, N, RWORK )
  374. IF( DNORM.GT.ZERO ) THEN
  375. RESULT( 6 ) = RESID / ( EPS * MAX( 1, M ) * DNORM )
  376. ELSE
  377. RESULT( 6 ) = ZERO
  378. END IF
  379. *
  380. * Deallocate all arrays
  381. *
  382. DEALLOCATE ( A, AF, Q, R, RWORK, WORK, T1, T2, DIAG,
  383. $ C, D, CF, DF )
  384. *
  385. RETURN
  386. *
  387. * End of ZUNHR_COL01
  388. *
  389. END