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.

zunt01.f 6.9 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248
  1. *> \brief \b ZUNT01
  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 ZUNT01( ROWCOL, M, N, U, LDU, WORK, LWORK, RWORK,
  12. * RESID )
  13. *
  14. * .. Scalar Arguments ..
  15. * CHARACTER ROWCOL
  16. * INTEGER LDU, LWORK, M, N
  17. * DOUBLE PRECISION RESID
  18. * ..
  19. * .. Array Arguments ..
  20. * DOUBLE PRECISION RWORK( * )
  21. * COMPLEX*16 U( LDU, * ), WORK( * )
  22. * ..
  23. *
  24. *
  25. *> \par Purpose:
  26. * =============
  27. *>
  28. *> \verbatim
  29. *>
  30. *> ZUNT01 checks that the matrix U is unitary by computing the ratio
  31. *>
  32. *> RESID = norm( I - U*U' ) / ( n * EPS ), if ROWCOL = 'R',
  33. *> or
  34. *> RESID = norm( I - U'*U ) / ( m * EPS ), if ROWCOL = 'C'.
  35. *>
  36. *> Alternatively, if there isn't sufficient workspace to form
  37. *> I - U*U' or I - U'*U, the ratio is computed as
  38. *>
  39. *> RESID = abs( I - U*U' ) / ( n * EPS ), if ROWCOL = 'R',
  40. *> or
  41. *> RESID = abs( I - U'*U ) / ( m * EPS ), if ROWCOL = 'C'.
  42. *>
  43. *> where EPS is the machine precision. ROWCOL is used only if m = n;
  44. *> if m > n, ROWCOL is assumed to be 'C', and if m < n, ROWCOL is
  45. *> assumed to be 'R'.
  46. *> \endverbatim
  47. *
  48. * Arguments:
  49. * ==========
  50. *
  51. *> \param[in] ROWCOL
  52. *> \verbatim
  53. *> ROWCOL is CHARACTER
  54. *> Specifies whether the rows or columns of U should be checked
  55. *> for orthogonality. Used only if M = N.
  56. *> = 'R': Check for orthogonal rows of U
  57. *> = 'C': Check for orthogonal columns of U
  58. *> \endverbatim
  59. *>
  60. *> \param[in] M
  61. *> \verbatim
  62. *> M is INTEGER
  63. *> The number of rows of the matrix U.
  64. *> \endverbatim
  65. *>
  66. *> \param[in] N
  67. *> \verbatim
  68. *> N is INTEGER
  69. *> The number of columns of the matrix U.
  70. *> \endverbatim
  71. *>
  72. *> \param[in] U
  73. *> \verbatim
  74. *> U is COMPLEX*16 array, dimension (LDU,N)
  75. *> The unitary matrix U. U is checked for orthogonal columns
  76. *> if m > n or if m = n and ROWCOL = 'C'. U is checked for
  77. *> orthogonal rows if m < n or if m = n and ROWCOL = 'R'.
  78. *> \endverbatim
  79. *>
  80. *> \param[in] LDU
  81. *> \verbatim
  82. *> LDU is INTEGER
  83. *> The leading dimension of the array U. LDU >= max(1,M).
  84. *> \endverbatim
  85. *>
  86. *> \param[out] WORK
  87. *> \verbatim
  88. *> WORK is COMPLEX*16 array, dimension (LWORK)
  89. *> \endverbatim
  90. *>
  91. *> \param[in] LWORK
  92. *> \verbatim
  93. *> LWORK is INTEGER
  94. *> The length of the array WORK. For best performance, LWORK
  95. *> should be at least N*N if ROWCOL = 'C' or M*M if
  96. *> ROWCOL = 'R', but the test will be done even if LWORK is 0.
  97. *> \endverbatim
  98. *>
  99. *> \param[out] RWORK
  100. *> \verbatim
  101. *> RWORK is DOUBLE PRECISION array, dimension (min(M,N))
  102. *> Used only if LWORK is large enough to use the Level 3 BLAS
  103. *> code.
  104. *> \endverbatim
  105. *>
  106. *> \param[out] RESID
  107. *> \verbatim
  108. *> RESID is DOUBLE PRECISION
  109. *> RESID = norm( I - U * U' ) / ( n * EPS ), if ROWCOL = 'R', or
  110. *> RESID = norm( I - U' * U ) / ( m * EPS ), if ROWCOL = 'C'.
  111. *> \endverbatim
  112. *
  113. * Authors:
  114. * ========
  115. *
  116. *> \author Univ. of Tennessee
  117. *> \author Univ. of California Berkeley
  118. *> \author Univ. of Colorado Denver
  119. *> \author NAG Ltd.
  120. *
  121. *> \date November 2011
  122. *
  123. *> \ingroup complex16_eig
  124. *
  125. * =====================================================================
  126. SUBROUTINE ZUNT01( ROWCOL, M, N, U, LDU, WORK, LWORK, RWORK,
  127. $ RESID )
  128. *
  129. * -- LAPACK test routine (version 3.4.0) --
  130. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  131. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  132. * November 2011
  133. *
  134. * .. Scalar Arguments ..
  135. CHARACTER ROWCOL
  136. INTEGER LDU, LWORK, M, N
  137. DOUBLE PRECISION RESID
  138. * ..
  139. * .. Array Arguments ..
  140. DOUBLE PRECISION RWORK( * )
  141. COMPLEX*16 U( LDU, * ), WORK( * )
  142. * ..
  143. *
  144. * =====================================================================
  145. *
  146. * .. Parameters ..
  147. DOUBLE PRECISION ZERO, ONE
  148. PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
  149. * ..
  150. * .. Local Scalars ..
  151. CHARACTER TRANSU
  152. INTEGER I, J, K, LDWORK, MNMIN
  153. DOUBLE PRECISION EPS
  154. COMPLEX*16 TMP, ZDUM
  155. * ..
  156. * .. External Functions ..
  157. LOGICAL LSAME
  158. DOUBLE PRECISION DLAMCH, ZLANSY
  159. COMPLEX*16 ZDOTC
  160. EXTERNAL LSAME, DLAMCH, ZLANSY, ZDOTC
  161. * ..
  162. * .. External Subroutines ..
  163. EXTERNAL ZHERK, ZLASET
  164. * ..
  165. * .. Intrinsic Functions ..
  166. INTRINSIC ABS, DBLE, DCMPLX, DIMAG, MAX, MIN
  167. * ..
  168. * .. Statement Functions ..
  169. DOUBLE PRECISION CABS1
  170. * ..
  171. * .. Statement Function definitions ..
  172. CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
  173. * ..
  174. * .. Executable Statements ..
  175. *
  176. RESID = ZERO
  177. *
  178. * Quick return if possible
  179. *
  180. IF( M.LE.0 .OR. N.LE.0 )
  181. $ RETURN
  182. *
  183. EPS = DLAMCH( 'Precision' )
  184. IF( M.LT.N .OR. ( M.EQ.N .AND. LSAME( ROWCOL, 'R' ) ) ) THEN
  185. TRANSU = 'N'
  186. K = N
  187. ELSE
  188. TRANSU = 'C'
  189. K = M
  190. END IF
  191. MNMIN = MIN( M, N )
  192. *
  193. IF( ( MNMIN+1 )*MNMIN.LE.LWORK ) THEN
  194. LDWORK = MNMIN
  195. ELSE
  196. LDWORK = 0
  197. END IF
  198. IF( LDWORK.GT.0 ) THEN
  199. *
  200. * Compute I - U*U' or I - U'*U.
  201. *
  202. CALL ZLASET( 'Upper', MNMIN, MNMIN, DCMPLX( ZERO ),
  203. $ DCMPLX( ONE ), WORK, LDWORK )
  204. CALL ZHERK( 'Upper', TRANSU, MNMIN, K, -ONE, U, LDU, ONE, WORK,
  205. $ LDWORK )
  206. *
  207. * Compute norm( I - U*U' ) / ( K * EPS ) .
  208. *
  209. RESID = ZLANSY( '1', 'Upper', MNMIN, WORK, LDWORK, RWORK )
  210. RESID = ( RESID / DBLE( K ) ) / EPS
  211. ELSE IF( TRANSU.EQ.'C' ) THEN
  212. *
  213. * Find the maximum element in abs( I - U'*U ) / ( m * EPS )
  214. *
  215. DO 20 J = 1, N
  216. DO 10 I = 1, J
  217. IF( I.NE.J ) THEN
  218. TMP = ZERO
  219. ELSE
  220. TMP = ONE
  221. END IF
  222. TMP = TMP - ZDOTC( M, U( 1, I ), 1, U( 1, J ), 1 )
  223. RESID = MAX( RESID, CABS1( TMP ) )
  224. 10 CONTINUE
  225. 20 CONTINUE
  226. RESID = ( RESID / DBLE( M ) ) / EPS
  227. ELSE
  228. *
  229. * Find the maximum element in abs( I - U*U' ) / ( n * EPS )
  230. *
  231. DO 40 J = 1, M
  232. DO 30 I = 1, J
  233. IF( I.NE.J ) THEN
  234. TMP = ZERO
  235. ELSE
  236. TMP = ONE
  237. END IF
  238. TMP = TMP - ZDOTC( N, U( J, 1 ), LDU, U( I, 1 ), LDU )
  239. RESID = MAX( RESID, CABS1( TMP ) )
  240. 30 CONTINUE
  241. 40 CONTINUE
  242. RESID = ( RESID / DBLE( N ) ) / EPS
  243. END IF
  244. RETURN
  245. *
  246. * End of ZUNT01
  247. *
  248. END