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.

dqrt04.f 6.7 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259
  1. *> \brief \b DQRT04
  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 DQRT04(M,N,NB,RESULT)
  12. *
  13. * .. Scalar Arguments ..
  14. * INTEGER M, N, NB, LDT
  15. * .. Return values ..
  16. * DOUBLE PRECISION RESULT(6)
  17. *
  18. *
  19. *> \par Purpose:
  20. * =============
  21. *>
  22. *> \verbatim
  23. *>
  24. *> DQRT04 tests DGEQRT and DGEMQRT.
  25. *> \endverbatim
  26. *
  27. * Arguments:
  28. * ==========
  29. *
  30. *> \param[in] M
  31. *> \verbatim
  32. *> M is INTEGER
  33. *> Number of rows in test matrix.
  34. *> \endverbatim
  35. *>
  36. *> \param[in] N
  37. *> \verbatim
  38. *> N is INTEGER
  39. *> Number of columns in test matrix.
  40. *> \endverbatim
  41. *>
  42. *> \param[in] NB
  43. *> \verbatim
  44. *> NB is INTEGER
  45. *> Block size of test matrix. NB <= Min(M,N).
  46. *> \endverbatim
  47. *>
  48. *> \param[out] RESULT
  49. *> \verbatim
  50. *> RESULT is DOUBLE PRECISION array, dimension (6)
  51. *> Results of each of the six tests below.
  52. *>
  53. *> RESULT(1) = | A - Q R |
  54. *> RESULT(2) = | I - Q^H Q |
  55. *> RESULT(3) = | Q C - Q C |
  56. *> RESULT(4) = | Q^H C - Q^H C |
  57. *> RESULT(5) = | C Q - C Q |
  58. *> RESULT(6) = | C Q^H - C Q^H |
  59. *> \endverbatim
  60. *
  61. * Authors:
  62. * ========
  63. *
  64. *> \author Univ. of Tennessee
  65. *> \author Univ. of California Berkeley
  66. *> \author Univ. of Colorado Denver
  67. *> \author NAG Ltd.
  68. *
  69. *> \date April 2012
  70. *
  71. *> \ingroup double_lin
  72. *
  73. * =====================================================================
  74. SUBROUTINE DQRT04(M,N,NB,RESULT)
  75. IMPLICIT NONE
  76. *
  77. * -- LAPACK test routine (version 3.7.0) --
  78. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  79. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  80. * April 2012
  81. *
  82. * .. Scalar Arguments ..
  83. INTEGER M, N, NB, LDT
  84. * .. Return values ..
  85. DOUBLE PRECISION RESULT(6)
  86. *
  87. * =====================================================================
  88. *
  89. * ..
  90. * .. Local allocatable arrays
  91. DOUBLE PRECISION, ALLOCATABLE :: AF(:,:), Q(:,:),
  92. $ R(:,:), RWORK(:), WORK( : ), T(:,:),
  93. $ CF(:,:), DF(:,:), A(:,:), C(:,:), D(:,:)
  94. *
  95. * .. Parameters ..
  96. DOUBLE PRECISION ONE, ZERO
  97. PARAMETER( ZERO = 0.0, ONE = 1.0 )
  98. * ..
  99. * .. Local Scalars ..
  100. INTEGER INFO, J, K, L, LWORK
  101. DOUBLE PRECISION ANORM, EPS, RESID, CNORM, DNORM
  102. * ..
  103. * .. Local Arrays ..
  104. INTEGER ISEED( 4 )
  105. * ..
  106. * .. External Functions ..
  107. DOUBLE PRECISION DLAMCH, DLANGE, DLANSY
  108. LOGICAL LSAME
  109. EXTERNAL DLAMCH, DLANGE, DLANSY, LSAME
  110. * ..
  111. * .. Intrinsic Functions ..
  112. INTRINSIC MAX, MIN
  113. * ..
  114. * .. Data statements ..
  115. DATA ISEED / 1988, 1989, 1990, 1991 /
  116. *
  117. EPS = DLAMCH( 'Epsilon' )
  118. K = MIN(M,N)
  119. L = MAX(M,N)
  120. LWORK = MAX(2,L)*MAX(2,L)*NB
  121. *
  122. * Dynamically allocate local arrays
  123. *
  124. ALLOCATE ( A(M,N), AF(M,N), Q(M,M), R(M,L), RWORK(L),
  125. $ WORK(LWORK), T(NB,N), C(M,N), CF(M,N),
  126. $ D(N,M), DF(N,M) )
  127. *
  128. * Put random numbers into A and copy to AF
  129. *
  130. LDT=NB
  131. DO J=1,N
  132. CALL DLARNV( 2, ISEED, M, A( 1, J ) )
  133. END DO
  134. CALL DLACPY( 'Full', M, N, A, M, AF, M )
  135. *
  136. * Factor the matrix A in the array AF.
  137. *
  138. CALL DGEQRT( M, N, NB, AF, M, T, LDT, WORK, INFO )
  139. *
  140. * Generate the m-by-m matrix Q
  141. *
  142. CALL DLASET( 'Full', M, M, ZERO, ONE, Q, M )
  143. CALL DGEMQRT( 'R', 'N', M, M, K, NB, AF, M, T, LDT, Q, M,
  144. $ WORK, INFO )
  145. *
  146. * Copy R
  147. *
  148. CALL DLASET( 'Full', M, N, ZERO, ZERO, R, M )
  149. CALL DLACPY( 'Upper', M, N, AF, M, R, M )
  150. *
  151. * Compute |R - Q'*A| / |A| and store in RESULT(1)
  152. *
  153. CALL DGEMM( 'T', 'N', M, N, M, -ONE, Q, M, A, M, ONE, R, M )
  154. ANORM = DLANGE( '1', M, N, A, M, RWORK )
  155. RESID = DLANGE( '1', M, N, R, M, RWORK )
  156. IF( ANORM.GT.ZERO ) THEN
  157. RESULT( 1 ) = RESID / (EPS*MAX(1,M)*ANORM)
  158. ELSE
  159. RESULT( 1 ) = ZERO
  160. END IF
  161. *
  162. * Compute |I - Q'*Q| and store in RESULT(2)
  163. *
  164. CALL DLASET( 'Full', M, M, ZERO, ONE, R, M )
  165. CALL DSYRK( 'U', 'C', M, M, -ONE, Q, M, ONE, R, M )
  166. RESID = DLANSY( '1', 'Upper', M, R, M, RWORK )
  167. RESULT( 2 ) = RESID / (EPS*MAX(1,M))
  168. *
  169. * Generate random m-by-n matrix C and a copy CF
  170. *
  171. DO J=1,N
  172. CALL DLARNV( 2, ISEED, M, C( 1, J ) )
  173. END DO
  174. CNORM = DLANGE( '1', M, N, C, M, RWORK)
  175. CALL DLACPY( 'Full', M, N, C, M, CF, M )
  176. *
  177. * Apply Q to C as Q*C
  178. *
  179. CALL DGEMQRT( 'L', 'N', M, N, K, NB, AF, M, T, NB, CF, M,
  180. $ WORK, INFO)
  181. *
  182. * Compute |Q*C - Q*C| / |C|
  183. *
  184. CALL DGEMM( 'N', 'N', M, N, M, -ONE, Q, M, C, M, ONE, CF, M )
  185. RESID = DLANGE( '1', M, N, CF, M, RWORK )
  186. IF( CNORM.GT.ZERO ) THEN
  187. RESULT( 3 ) = RESID / (EPS*MAX(1,M)*CNORM)
  188. ELSE
  189. RESULT( 3 ) = ZERO
  190. END IF
  191. *
  192. * Copy C into CF again
  193. *
  194. CALL DLACPY( 'Full', M, N, C, M, CF, M )
  195. *
  196. * Apply Q to C as QT*C
  197. *
  198. CALL DGEMQRT( 'L', 'T', M, N, K, NB, AF, M, T, NB, CF, M,
  199. $ WORK, INFO)
  200. *
  201. * Compute |QT*C - QT*C| / |C|
  202. *
  203. CALL DGEMM( 'T', 'N', M, N, M, -ONE, Q, M, C, M, ONE, CF, M )
  204. RESID = DLANGE( '1', M, N, CF, M, RWORK )
  205. IF( CNORM.GT.ZERO ) THEN
  206. RESULT( 4 ) = RESID / (EPS*MAX(1,M)*CNORM)
  207. ELSE
  208. RESULT( 4 ) = ZERO
  209. END IF
  210. *
  211. * Generate random n-by-m matrix D and a copy DF
  212. *
  213. DO J=1,M
  214. CALL DLARNV( 2, ISEED, N, D( 1, J ) )
  215. END DO
  216. DNORM = DLANGE( '1', N, M, D, N, RWORK)
  217. CALL DLACPY( 'Full', N, M, D, N, DF, N )
  218. *
  219. * Apply Q to D as D*Q
  220. *
  221. CALL DGEMQRT( 'R', 'N', N, M, K, NB, AF, M, T, NB, DF, N,
  222. $ WORK, INFO)
  223. *
  224. * Compute |D*Q - D*Q| / |D|
  225. *
  226. CALL DGEMM( 'N', 'N', N, M, M, -ONE, D, N, Q, M, ONE, DF, N )
  227. RESID = DLANGE( '1', N, M, DF, N, RWORK )
  228. IF( CNORM.GT.ZERO ) THEN
  229. RESULT( 5 ) = RESID / (EPS*MAX(1,M)*DNORM)
  230. ELSE
  231. RESULT( 5 ) = ZERO
  232. END IF
  233. *
  234. * Copy D into DF again
  235. *
  236. CALL DLACPY( 'Full', N, M, D, N, DF, N )
  237. *
  238. * Apply Q to D as D*QT
  239. *
  240. CALL DGEMQRT( 'R', 'T', N, M, K, NB, AF, M, T, NB, DF, N,
  241. $ WORK, INFO)
  242. *
  243. * Compute |D*QT - D*QT| / |D|
  244. *
  245. CALL DGEMM( 'N', 'T', N, M, M, -ONE, D, N, Q, M, ONE, DF, N )
  246. RESID = DLANGE( '1', N, M, DF, N, RWORK )
  247. IF( CNORM.GT.ZERO ) THEN
  248. RESULT( 6 ) = RESID / (EPS*MAX(1,M)*DNORM)
  249. ELSE
  250. RESULT( 6 ) = ZERO
  251. END IF
  252. *
  253. * Deallocate all arrays
  254. *
  255. DEALLOCATE ( A, AF, Q, R, RWORK, WORK, T, C, D, CF, DF)
  256. *
  257. RETURN
  258. END