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.

dchktz.f 11 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361
  1. *> \brief \b DCHKTZ
  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 DCHKTZ( DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A,
  12. * COPYA, S, TAU, WORK, NOUT )
  13. *
  14. * .. Scalar Arguments ..
  15. * LOGICAL TSTERR
  16. * INTEGER NM, NN, NOUT
  17. * DOUBLE PRECISION THRESH
  18. * ..
  19. * .. Array Arguments ..
  20. * LOGICAL DOTYPE( * )
  21. * INTEGER MVAL( * ), NVAL( * )
  22. * DOUBLE PRECISION A( * ), COPYA( * ), S( * ),
  23. * $ TAU( * ), WORK( * )
  24. * ..
  25. *
  26. *
  27. *> \par Purpose:
  28. * =============
  29. *>
  30. *> \verbatim
  31. *>
  32. *> DCHKTZ tests DTZRQF and STZRZF.
  33. *> \endverbatim
  34. *
  35. * Arguments:
  36. * ==========
  37. *
  38. *> \param[in] DOTYPE
  39. *> \verbatim
  40. *> DOTYPE is LOGICAL array, dimension (NTYPES)
  41. *> The matrix types to be used for testing. Matrices of type j
  42. *> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
  43. *> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
  44. *> \endverbatim
  45. *>
  46. *> \param[in] NM
  47. *> \verbatim
  48. *> NM is INTEGER
  49. *> The number of values of M contained in the vector MVAL.
  50. *> \endverbatim
  51. *>
  52. *> \param[in] MVAL
  53. *> \verbatim
  54. *> MVAL is INTEGER array, dimension (NM)
  55. *> The values of the matrix row dimension M.
  56. *> \endverbatim
  57. *>
  58. *> \param[in] NN
  59. *> \verbatim
  60. *> NN is INTEGER
  61. *> The number of values of N contained in the vector NVAL.
  62. *> \endverbatim
  63. *>
  64. *> \param[in] NVAL
  65. *> \verbatim
  66. *> NVAL is INTEGER array, dimension (NN)
  67. *> The values of the matrix column dimension N.
  68. *> \endverbatim
  69. *>
  70. *> \param[in] THRESH
  71. *> \verbatim
  72. *> THRESH is DOUBLE PRECISION
  73. *> The threshold value for the test ratios. A result is
  74. *> included in the output file if RESULT >= THRESH. To have
  75. *> every test ratio printed, use THRESH = 0.
  76. *> \endverbatim
  77. *>
  78. *> \param[in] TSTERR
  79. *> \verbatim
  80. *> TSTERR is LOGICAL
  81. *> Flag that indicates whether error exits are to be tested.
  82. *> \endverbatim
  83. *>
  84. *> \param[out] A
  85. *> \verbatim
  86. *> A is DOUBLE PRECISION array, dimension (MMAX*NMAX)
  87. *> where MMAX is the maximum value of M in MVAL and NMAX is the
  88. *> maximum value of N in NVAL.
  89. *> \endverbatim
  90. *>
  91. *> \param[out] COPYA
  92. *> \verbatim
  93. *> COPYA is DOUBLE PRECISION array, dimension (MMAX*NMAX)
  94. *> \endverbatim
  95. *>
  96. *> \param[out] S
  97. *> \verbatim
  98. *> S is DOUBLE PRECISION array, dimension
  99. *> (min(MMAX,NMAX))
  100. *> \endverbatim
  101. *>
  102. *> \param[out] TAU
  103. *> \verbatim
  104. *> TAU is DOUBLE PRECISION array, dimension (MMAX)
  105. *> \endverbatim
  106. *>
  107. *> \param[out] WORK
  108. *> \verbatim
  109. *> WORK is DOUBLE PRECISION array, dimension
  110. *> (MMAX*NMAX + 4*NMAX + MMAX)
  111. *> \endverbatim
  112. *>
  113. *> \param[in] NOUT
  114. *> \verbatim
  115. *> NOUT is INTEGER
  116. *> The unit number for output.
  117. *> \endverbatim
  118. *
  119. * Authors:
  120. * ========
  121. *
  122. *> \author Univ. of Tennessee
  123. *> \author Univ. of California Berkeley
  124. *> \author Univ. of Colorado Denver
  125. *> \author NAG Ltd.
  126. *
  127. *> \date November 2011
  128. *
  129. *> \ingroup double_lin
  130. *
  131. * =====================================================================
  132. SUBROUTINE DCHKTZ( DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A,
  133. $ COPYA, S, TAU, WORK, NOUT )
  134. *
  135. * -- LAPACK test routine (version 3.4.0) --
  136. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  137. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  138. * November 2011
  139. *
  140. * .. Scalar Arguments ..
  141. LOGICAL TSTERR
  142. INTEGER NM, NN, NOUT
  143. DOUBLE PRECISION THRESH
  144. * ..
  145. * .. Array Arguments ..
  146. LOGICAL DOTYPE( * )
  147. INTEGER MVAL( * ), NVAL( * )
  148. DOUBLE PRECISION A( * ), COPYA( * ), S( * ),
  149. $ TAU( * ), WORK( * )
  150. * ..
  151. *
  152. * =====================================================================
  153. *
  154. * .. Parameters ..
  155. INTEGER NTYPES
  156. PARAMETER ( NTYPES = 3 )
  157. INTEGER NTESTS
  158. PARAMETER ( NTESTS = 6 )
  159. DOUBLE PRECISION ONE, ZERO
  160. PARAMETER ( ONE = 1.0D0, ZERO = 0.0D0 )
  161. * ..
  162. * .. Local Scalars ..
  163. CHARACTER*3 PATH
  164. INTEGER I, IM, IMODE, IN, INFO, K, LDA, LWORK, M,
  165. $ MNMIN, MODE, N, NERRS, NFAIL, NRUN
  166. DOUBLE PRECISION EPS
  167. * ..
  168. * .. Local Arrays ..
  169. INTEGER ISEED( 4 ), ISEEDY( 4 )
  170. DOUBLE PRECISION RESULT( NTESTS )
  171. * ..
  172. * .. External Functions ..
  173. DOUBLE PRECISION DLAMCH, DQRT12, DRZT01, DRZT02, DTZT01, DTZT02
  174. EXTERNAL DLAMCH, DQRT12, DRZT01, DRZT02, DTZT01, DTZT02
  175. * ..
  176. * .. External Subroutines ..
  177. EXTERNAL ALAHD, ALASUM, DERRTZ, DGEQR2, DLACPY, DLAORD,
  178. $ DLASET, DLATMS, DTZRQF, DTZRZF
  179. * ..
  180. * .. Intrinsic Functions ..
  181. INTRINSIC MAX, MIN
  182. * ..
  183. * .. Scalars in Common ..
  184. LOGICAL LERR, OK
  185. CHARACTER*32 SRNAMT
  186. INTEGER INFOT, IOUNIT
  187. * ..
  188. * .. Common blocks ..
  189. COMMON / INFOC / INFOT, IOUNIT, OK, LERR
  190. COMMON / SRNAMC / SRNAMT
  191. * ..
  192. * .. Data statements ..
  193. DATA ISEEDY / 1988, 1989, 1990, 1991 /
  194. * ..
  195. * .. Executable Statements ..
  196. *
  197. * Initialize constants and the random number seed.
  198. *
  199. PATH( 1: 1 ) = 'Double precision'
  200. PATH( 2: 3 ) = 'TZ'
  201. NRUN = 0
  202. NFAIL = 0
  203. NERRS = 0
  204. DO 10 I = 1, 4
  205. ISEED( I ) = ISEEDY( I )
  206. 10 CONTINUE
  207. EPS = DLAMCH( 'Epsilon' )
  208. *
  209. * Test the error exits
  210. *
  211. IF( TSTERR )
  212. $ CALL DERRTZ( PATH, NOUT )
  213. INFOT = 0
  214. *
  215. DO 70 IM = 1, NM
  216. *
  217. * Do for each value of M in MVAL.
  218. *
  219. M = MVAL( IM )
  220. LDA = MAX( 1, M )
  221. *
  222. DO 60 IN = 1, NN
  223. *
  224. * Do for each value of N in NVAL for which M .LE. N.
  225. *
  226. N = NVAL( IN )
  227. MNMIN = MIN( M, N )
  228. LWORK = MAX( 1, N*N+4*M+N, M*N+2*MNMIN+4*N )
  229. *
  230. IF( M.LE.N ) THEN
  231. DO 50 IMODE = 1, NTYPES
  232. IF( .NOT.DOTYPE( IMODE ) )
  233. $ GO TO 50
  234. *
  235. * Do for each type of singular value distribution.
  236. * 0: zero matrix
  237. * 1: one small singular value
  238. * 2: exponential distribution
  239. *
  240. MODE = IMODE - 1
  241. *
  242. * Test DTZRQF
  243. *
  244. * Generate test matrix of size m by n using
  245. * singular value distribution indicated by `mode'.
  246. *
  247. IF( MODE.EQ.0 ) THEN
  248. CALL DLASET( 'Full', M, N, ZERO, ZERO, A, LDA )
  249. DO 20 I = 1, MNMIN
  250. S( I ) = ZERO
  251. 20 CONTINUE
  252. ELSE
  253. CALL DLATMS( M, N, 'Uniform', ISEED,
  254. $ 'Nonsymmetric', S, IMODE,
  255. $ ONE / EPS, ONE, M, N, 'No packing', A,
  256. $ LDA, WORK, INFO )
  257. CALL DGEQR2( M, N, A, LDA, WORK, WORK( MNMIN+1 ),
  258. $ INFO )
  259. CALL DLASET( 'Lower', M-1, N, ZERO, ZERO, A( 2 ),
  260. $ LDA )
  261. CALL DLAORD( 'Decreasing', MNMIN, S, 1 )
  262. END IF
  263. *
  264. * Save A and its singular values
  265. *
  266. CALL DLACPY( 'All', M, N, A, LDA, COPYA, LDA )
  267. *
  268. * Call DTZRQF to reduce the upper trapezoidal matrix to
  269. * upper triangular form.
  270. *
  271. SRNAMT = 'DTZRQF'
  272. CALL DTZRQF( M, N, A, LDA, TAU, INFO )
  273. *
  274. * Compute norm(svd(a) - svd(r))
  275. *
  276. RESULT( 1 ) = DQRT12( M, M, A, LDA, S, WORK,
  277. $ LWORK )
  278. *
  279. * Compute norm( A - R*Q )
  280. *
  281. RESULT( 2 ) = DTZT01( M, N, COPYA, A, LDA, TAU, WORK,
  282. $ LWORK )
  283. *
  284. * Compute norm(Q'*Q - I).
  285. *
  286. RESULT( 3 ) = DTZT02( M, N, A, LDA, TAU, WORK, LWORK )
  287. *
  288. * Test DTZRZF
  289. *
  290. * Generate test matrix of size m by n using
  291. * singular value distribution indicated by `mode'.
  292. *
  293. IF( MODE.EQ.0 ) THEN
  294. CALL DLASET( 'Full', M, N, ZERO, ZERO, A, LDA )
  295. DO 30 I = 1, MNMIN
  296. S( I ) = ZERO
  297. 30 CONTINUE
  298. ELSE
  299. CALL DLATMS( M, N, 'Uniform', ISEED,
  300. $ 'Nonsymmetric', S, IMODE,
  301. $ ONE / EPS, ONE, M, N, 'No packing', A,
  302. $ LDA, WORK, INFO )
  303. CALL DGEQR2( M, N, A, LDA, WORK, WORK( MNMIN+1 ),
  304. $ INFO )
  305. CALL DLASET( 'Lower', M-1, N, ZERO, ZERO, A( 2 ),
  306. $ LDA )
  307. CALL DLAORD( 'Decreasing', MNMIN, S, 1 )
  308. END IF
  309. *
  310. * Save A and its singular values
  311. *
  312. CALL DLACPY( 'All', M, N, A, LDA, COPYA, LDA )
  313. *
  314. * Call DTZRZF to reduce the upper trapezoidal matrix to
  315. * upper triangular form.
  316. *
  317. SRNAMT = 'DTZRZF'
  318. CALL DTZRZF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
  319. *
  320. * Compute norm(svd(a) - svd(r))
  321. *
  322. RESULT( 4 ) = DQRT12( M, M, A, LDA, S, WORK,
  323. $ LWORK )
  324. *
  325. * Compute norm( A - R*Q )
  326. *
  327. RESULT( 5 ) = DRZT01( M, N, COPYA, A, LDA, TAU, WORK,
  328. $ LWORK )
  329. *
  330. * Compute norm(Q'*Q - I).
  331. *
  332. RESULT( 6 ) = DRZT02( M, N, A, LDA, TAU, WORK, LWORK )
  333. *
  334. * Print information about the tests that did not pass
  335. * the threshold.
  336. *
  337. DO 40 K = 1, 6
  338. IF( RESULT( K ).GE.THRESH ) THEN
  339. IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
  340. $ CALL ALAHD( NOUT, PATH )
  341. WRITE( NOUT, FMT = 9999 )M, N, IMODE, K,
  342. $ RESULT( K )
  343. NFAIL = NFAIL + 1
  344. END IF
  345. 40 CONTINUE
  346. NRUN = NRUN + 6
  347. 50 CONTINUE
  348. END IF
  349. 60 CONTINUE
  350. 70 CONTINUE
  351. *
  352. * Print a summary of the results.
  353. *
  354. CALL ALASUM( PATH, NOUT, NFAIL, NRUN, NERRS )
  355. *
  356. 9999 FORMAT( ' M =', I5, ', N =', I5, ', type ', I2, ', test ', I2,
  357. $ ', ratio =', G12.5 )
  358. *
  359. * End if DCHKTZ
  360. *
  361. END