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.

sorhr_col01.f 12 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415
  1. *> \brief \b SORHR_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 SORHR_COL01( M, N, MB1, NB1, NB2, RESULT )
  12. *
  13. * .. Scalar Arguments ..
  14. * INTEGER M, N, MB1, NB1, NB2
  15. * .. Return values ..
  16. * REAL RESULT(6)
  17. *
  18. *
  19. *> \par Purpose:
  20. * =============
  21. *>
  22. *> \verbatim
  23. *>
  24. *> SORHR_COL01 tests SORGTSQR and SORHR_COL using SLATSQR, SGEMQRT.
  25. *> Therefore, SLATSQR (part of SGEQR), SGEMQRT (part of SGEMQR)
  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 REAL array, dimension (6)
  64. *> Results of each of the six tests below.
  65. *>
  66. *> A is a m-by-n test input matrix to be factored.
  67. *> so that A = Q_gr * ( R )
  68. *> ( 0 ),
  69. *>
  70. *> Q_qr is an implicit m-by-m orthogonal Q matrix, the result
  71. *> of factorization in blocked WY-representation,
  72. *> stored in SGEQRT output format.
  73. *>
  74. *> R is a n-by-n upper-triangular matrix,
  75. *>
  76. *> 0 is a (m-n)-by-n zero matrix,
  77. *>
  78. *> Q is an explicit m-by-m orthogonal matrix Q = Q_gr * I
  79. *>
  80. *> C is an m-by-n random matrix,
  81. *>
  82. *> D is an n-by-m random matrix.
  83. *>
  84. *> The six tests are:
  85. *>
  86. *> RESULT(1) = |R - (Q**H) * A| / ( eps * m * |A| )
  87. *> is equivalent to test for | A - Q * R | / (eps * m * |A|),
  88. *>
  89. *> RESULT(2) = |I - (Q**H) * Q| / ( eps * m ),
  90. *>
  91. *> RESULT(3) = | Q_qr * C - Q * C | / (eps * m * |C|),
  92. *>
  93. *> RESULT(4) = | (Q_gr**H) * C - (Q**H) * C | / (eps * m * |C|)
  94. *>
  95. *> RESULT(5) = | D * Q_qr - D * Q | / (eps * m * |D|)
  96. *>
  97. *> RESULT(6) = | D * (Q_qr**H) - D * (Q**H) | / (eps * m * |D|),
  98. *>
  99. *> where:
  100. *> Q_qr * C, (Q_gr**H) * C, D * Q_qr, D * (Q_qr**H) are
  101. *> computed using SGEMQRT,
  102. *>
  103. *> Q * C, (Q**H) * C, D * Q, D * (Q**H) are
  104. *> computed using SGEMM.
  105. *> \endverbatim
  106. *
  107. * Authors:
  108. * ========
  109. *
  110. *> \author Univ. of Tennessee
  111. *> \author Univ. of California Berkeley
  112. *> \author Univ. of Colorado Denver
  113. *> \author NAG Ltd.
  114. *
  115. *> \ingroup single_lin
  116. *
  117. * =====================================================================
  118. SUBROUTINE SORHR_COL01( M, N, MB1, NB1, NB2, RESULT )
  119. IMPLICIT NONE
  120. *
  121. * -- LAPACK test routine --
  122. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  123. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  124. *
  125. * .. Scalar Arguments ..
  126. INTEGER M, N, MB1, NB1, NB2
  127. * .. Return values ..
  128. REAL RESULT(6)
  129. *
  130. * =====================================================================
  131. *
  132. * ..
  133. * .. Local allocatable arrays
  134. REAL , ALLOCATABLE :: A(:,:), AF(:,:), Q(:,:), R(:,:),
  135. $ RWORK(:), WORK( : ), T1(:,:), T2(:,:), DIAG(:),
  136. $ C(:,:), CF(:,:), D(:,:), DF(:,:)
  137. *
  138. * .. Parameters ..
  139. REAL ONE, ZERO
  140. PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
  141. * ..
  142. * .. Local Scalars ..
  143. LOGICAL TESTZEROS
  144. INTEGER INFO, I, J, K, L, LWORK, NB1_UB, NB2_UB, NRB
  145. REAL ANORM, EPS, RESID, CNORM, DNORM
  146. * ..
  147. * .. Local Arrays ..
  148. INTEGER ISEED( 4 )
  149. REAL WORKQUERY( 1 )
  150. * ..
  151. * .. External Functions ..
  152. REAL SLAMCH, SLANGE, SLANSY
  153. EXTERNAL SLAMCH, SLANGE, SLANSY
  154. * ..
  155. * .. External Subroutines ..
  156. EXTERNAL SLACPY, SLARNV, SLASET, SLATSQR, SORHR_COL,
  157. $ SORGTSQR, SSCAL, SGEMM, SGEMQRT, SSYRK
  158. * ..
  159. * .. Intrinsic Functions ..
  160. INTRINSIC CEILING, REAL, MAX, MIN
  161. * ..
  162. * .. Scalars in Common ..
  163. CHARACTER(LEN=32) SRNAMT
  164. * ..
  165. * .. Common blocks ..
  166. COMMON / SRMNAMC / SRNAMT
  167. * ..
  168. * .. Data statements ..
  169. DATA ISEED / 1988, 1989, 1990, 1991 /
  170. *
  171. * TEST MATRICES WITH HALF OF MATRIX BEING ZEROS
  172. *
  173. TESTZEROS = .FALSE.
  174. *
  175. EPS = SLAMCH( 'Epsilon' )
  176. K = MIN( M, N )
  177. L = MAX( M, N, 1)
  178. *
  179. * Dynamically allocate local arrays
  180. *
  181. ALLOCATE ( A(M,N), AF(M,N), Q(L,L), R(M,L), RWORK(L),
  182. $ C(M,N), CF(M,N),
  183. $ D(N,M), DF(N,M) )
  184. *
  185. * Put random numbers into A and copy to AF
  186. *
  187. DO J = 1, N
  188. CALL SLARNV( 2, ISEED, M, A( 1, J ) )
  189. END DO
  190. IF( TESTZEROS ) THEN
  191. IF( M.GE.4 ) THEN
  192. DO J = 1, N
  193. CALL SLARNV( 2, ISEED, M/2, A( M/4, J ) )
  194. END DO
  195. END IF
  196. END IF
  197. CALL SLACPY( 'Full', M, N, A, M, AF, M )
  198. *
  199. * Number of row blocks in SLATSQR
  200. *
  201. NRB = MAX( 1, CEILING( REAL( M - N ) / REAL( MB1 - N ) ) )
  202. *
  203. ALLOCATE ( T1( NB1, N * NRB ) )
  204. ALLOCATE ( T2( NB2, N ) )
  205. ALLOCATE ( DIAG( N ) )
  206. *
  207. * Begin determine LWORK for the array WORK and allocate memory.
  208. *
  209. * SLATSQR requires NB1 to be bounded by N.
  210. *
  211. NB1_UB = MIN( NB1, N)
  212. *
  213. * SGEMQRT requires NB2 to be bounded by N.
  214. *
  215. NB2_UB = MIN( NB2, N)
  216. *
  217. CALL SLATSQR( M, N, MB1, NB1_UB, AF, M, T1, NB1,
  218. $ WORKQUERY, -1, INFO )
  219. LWORK = INT( WORKQUERY( 1 ) )
  220. CALL SORGTSQR( M, N, MB1, NB1, AF, M, T1, NB1, WORKQUERY, -1,
  221. $ INFO )
  222. LWORK = MAX( LWORK, INT( WORKQUERY( 1 ) ) )
  223. *
  224. * In SGEMQRT, WORK is N*NB2_UB if SIDE = 'L',
  225. * or M*NB2_UB if SIDE = 'R'.
  226. *
  227. LWORK = MAX( LWORK, NB2_UB * N, NB2_UB * M )
  228. *
  229. ALLOCATE ( WORK( LWORK ) )
  230. *
  231. * End allocate memory for WORK.
  232. *
  233. *
  234. * Begin Householder reconstruction routines
  235. *
  236. * Factor the matrix A in the array AF.
  237. *
  238. SRNAMT = 'SLATSQR'
  239. CALL SLATSQR( M, N, MB1, NB1_UB, AF, M, T1, NB1, WORK, LWORK,
  240. $ INFO )
  241. *
  242. * Copy the factor R into the array R.
  243. *
  244. SRNAMT = 'SLACPY'
  245. CALL SLACPY( 'U', N, N, AF, M, R, M )
  246. *
  247. * Reconstruct the orthogonal matrix Q.
  248. *
  249. SRNAMT = 'SORGTSQR'
  250. CALL SORGTSQR( M, N, MB1, NB1, AF, M, T1, NB1, WORK, LWORK,
  251. $ INFO )
  252. *
  253. * Perform the Householder reconstruction, the result is stored
  254. * the arrays AF and T2.
  255. *
  256. SRNAMT = 'SORHR_COL'
  257. CALL SORHR_COL( M, N, NB2, AF, M, T2, NB2, DIAG, INFO )
  258. *
  259. * Compute the factor R_hr corresponding to the Householder
  260. * reconstructed Q_hr and place it in the upper triangle of AF to
  261. * match the Q storage format in SGEQRT. R_hr = R_tsqr * S,
  262. * this means changing the sign of I-th row of the matrix R_tsqr
  263. * according to sign of of I-th diagonal element DIAG(I) of the
  264. * matrix S.
  265. *
  266. SRNAMT = 'SLACPY'
  267. CALL SLACPY( 'U', N, N, R, M, AF, M )
  268. *
  269. DO I = 1, N
  270. IF( DIAG( I ).EQ.-ONE ) THEN
  271. CALL SSCAL( N+1-I, -ONE, AF( I, I ), M )
  272. END IF
  273. END DO
  274. *
  275. * End Householder reconstruction routines.
  276. *
  277. *
  278. * Generate the m-by-m matrix Q
  279. *
  280. CALL SLASET( 'Full', M, M, ZERO, ONE, Q, M )
  281. *
  282. SRNAMT = 'SGEMQRT'
  283. CALL SGEMQRT( 'L', 'N', M, M, K, NB2_UB, AF, M, T2, NB2, Q, M,
  284. $ WORK, INFO )
  285. *
  286. * Copy R
  287. *
  288. CALL SLASET( 'Full', M, N, ZERO, ZERO, R, M )
  289. *
  290. CALL SLACPY( 'Upper', M, N, AF, M, R, M )
  291. *
  292. * TEST 1
  293. * Compute |R - (Q**T)*A| / ( eps * m * |A| ) and store in RESULT(1)
  294. *
  295. CALL SGEMM( 'T', 'N', M, N, M, -ONE, Q, M, A, M, ONE, R, M )
  296. *
  297. ANORM = SLANGE( '1', M, N, A, M, RWORK )
  298. RESID = SLANGE( '1', M, N, R, M, RWORK )
  299. IF( ANORM.GT.ZERO ) THEN
  300. RESULT( 1 ) = RESID / ( EPS * MAX( 1, M ) * ANORM )
  301. ELSE
  302. RESULT( 1 ) = ZERO
  303. END IF
  304. *
  305. * TEST 2
  306. * Compute |I - (Q**T)*Q| / ( eps * m ) and store in RESULT(2)
  307. *
  308. CALL SLASET( 'Full', M, M, ZERO, ONE, R, M )
  309. CALL SSYRK( 'U', 'T', M, M, -ONE, Q, M, ONE, R, M )
  310. RESID = SLANSY( '1', 'Upper', M, R, M, RWORK )
  311. RESULT( 2 ) = RESID / ( EPS * MAX( 1, M ) )
  312. *
  313. * Generate random m-by-n matrix C
  314. *
  315. DO J = 1, N
  316. CALL SLARNV( 2, ISEED, M, C( 1, J ) )
  317. END DO
  318. CNORM = SLANGE( '1', M, N, C, M, RWORK )
  319. CALL SLACPY( 'Full', M, N, C, M, CF, M )
  320. *
  321. * Apply Q to C as Q*C = CF
  322. *
  323. SRNAMT = 'SGEMQRT'
  324. CALL SGEMQRT( 'L', 'N', M, N, K, NB2_UB, AF, M, T2, NB2, CF, M,
  325. $ WORK, INFO )
  326. *
  327. * TEST 3
  328. * Compute |CF - Q*C| / ( eps * m * |C| )
  329. *
  330. CALL SGEMM( 'N', 'N', M, N, M, -ONE, Q, M, C, M, ONE, CF, M )
  331. RESID = SLANGE( '1', M, N, CF, M, RWORK )
  332. IF( CNORM.GT.ZERO ) THEN
  333. RESULT( 3 ) = RESID / ( EPS * MAX( 1, M ) * CNORM )
  334. ELSE
  335. RESULT( 3 ) = ZERO
  336. END IF
  337. *
  338. * Copy C into CF again
  339. *
  340. CALL SLACPY( 'Full', M, N, C, M, CF, M )
  341. *
  342. * Apply Q to C as (Q**T)*C = CF
  343. *
  344. SRNAMT = 'SGEMQRT'
  345. CALL SGEMQRT( 'L', 'T', M, N, K, NB2_UB, AF, M, T2, NB2, CF, M,
  346. $ WORK, INFO )
  347. *
  348. * TEST 4
  349. * Compute |CF - (Q**T)*C| / ( eps * m * |C|)
  350. *
  351. CALL SGEMM( 'T', 'N', M, N, M, -ONE, Q, M, C, M, ONE, CF, M )
  352. RESID = SLANGE( '1', M, N, CF, M, RWORK )
  353. IF( CNORM.GT.ZERO ) THEN
  354. RESULT( 4 ) = RESID / ( EPS * MAX( 1, M ) * CNORM )
  355. ELSE
  356. RESULT( 4 ) = ZERO
  357. END IF
  358. *
  359. * Generate random n-by-m matrix D and a copy DF
  360. *
  361. DO J = 1, M
  362. CALL SLARNV( 2, ISEED, N, D( 1, J ) )
  363. END DO
  364. DNORM = SLANGE( '1', N, M, D, N, RWORK )
  365. CALL SLACPY( 'Full', N, M, D, N, DF, N )
  366. *
  367. * Apply Q to D as D*Q = DF
  368. *
  369. SRNAMT = 'SGEMQRT'
  370. CALL SGEMQRT( 'R', 'N', N, M, K, NB2_UB, AF, M, T2, NB2, DF, N,
  371. $ WORK, INFO )
  372. *
  373. * TEST 5
  374. * Compute |DF - D*Q| / ( eps * m * |D| )
  375. *
  376. CALL SGEMM( 'N', 'N', N, M, M, -ONE, D, N, Q, M, ONE, DF, N )
  377. RESID = SLANGE( '1', N, M, DF, N, RWORK )
  378. IF( DNORM.GT.ZERO ) THEN
  379. RESULT( 5 ) = RESID / ( EPS * MAX( 1, M ) * DNORM )
  380. ELSE
  381. RESULT( 5 ) = ZERO
  382. END IF
  383. *
  384. * Copy D into DF again
  385. *
  386. CALL SLACPY( 'Full', N, M, D, N, DF, N )
  387. *
  388. * Apply Q to D as D*QT = DF
  389. *
  390. SRNAMT = 'SGEMQRT'
  391. CALL SGEMQRT( 'R', 'T', N, M, K, NB2_UB, AF, M, T2, NB2, DF, N,
  392. $ WORK, INFO )
  393. *
  394. * TEST 6
  395. * Compute |DF - D*(Q**T)| / ( eps * m * |D| )
  396. *
  397. CALL SGEMM( 'N', 'T', N, M, M, -ONE, D, N, Q, M, ONE, DF, N )
  398. RESID = SLANGE( '1', N, M, DF, N, RWORK )
  399. IF( DNORM.GT.ZERO ) THEN
  400. RESULT( 6 ) = RESID / ( EPS * MAX( 1, M ) * DNORM )
  401. ELSE
  402. RESULT( 6 ) = ZERO
  403. END IF
  404. *
  405. * Deallocate all arrays
  406. *
  407. DEALLOCATE ( A, AF, Q, R, RWORK, WORK, T1, T2, DIAG,
  408. $ C, D, CF, DF )
  409. *
  410. RETURN
  411. *
  412. * End of SORHR_COL01
  413. *
  414. END