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.

dort03.f 7.6 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278
  1. *> \brief \b DORT03
  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 DORT03( RC, MU, MV, N, K, U, LDU, V, LDV, WORK, LWORK,
  12. * RESULT, INFO )
  13. *
  14. * .. Scalar Arguments ..
  15. * CHARACTER*( * ) RC
  16. * INTEGER INFO, K, LDU, LDV, LWORK, MU, MV, N
  17. * DOUBLE PRECISION RESULT
  18. * ..
  19. * .. Array Arguments ..
  20. * DOUBLE PRECISION U( LDU, * ), V( LDV, * ), WORK( * )
  21. * ..
  22. *
  23. *
  24. *> \par Purpose:
  25. * =============
  26. *>
  27. *> \verbatim
  28. *>
  29. *> DORT03 compares two orthogonal matrices U and V to see if their
  30. *> corresponding rows or columns span the same spaces. The rows are
  31. *> checked if RC = 'R', and the columns are checked if RC = 'C'.
  32. *>
  33. *> RESULT is the maximum of
  34. *>
  35. *> | V*V' - I | / ( MV ulp ), if RC = 'R', or
  36. *>
  37. *> | V'*V - I | / ( MV ulp ), if RC = 'C',
  38. *>
  39. *> and the maximum over rows (or columns) 1 to K of
  40. *>
  41. *> | U(i) - S*V(i) |/ ( N ulp )
  42. *>
  43. *> where S is +-1 (chosen to minimize the expression), U(i) is the i-th
  44. *> row (column) of U, and V(i) is the i-th row (column) of V.
  45. *> \endverbatim
  46. *
  47. * Arguments:
  48. * ==========
  49. *
  50. *> \param[in] RC
  51. *> \verbatim
  52. *> RC is CHARACTER*1
  53. *> If RC = 'R' the rows of U and V are to be compared.
  54. *> If RC = 'C' the columns of U and V are to be compared.
  55. *> \endverbatim
  56. *>
  57. *> \param[in] MU
  58. *> \verbatim
  59. *> MU is INTEGER
  60. *> The number of rows of U if RC = 'R', and the number of
  61. *> columns if RC = 'C'. If MU = 0 DORT03 does nothing.
  62. *> MU must be at least zero.
  63. *> \endverbatim
  64. *>
  65. *> \param[in] MV
  66. *> \verbatim
  67. *> MV is INTEGER
  68. *> The number of rows of V if RC = 'R', and the number of
  69. *> columns if RC = 'C'. If MV = 0 DORT03 does nothing.
  70. *> MV must be at least zero.
  71. *> \endverbatim
  72. *>
  73. *> \param[in] N
  74. *> \verbatim
  75. *> N is INTEGER
  76. *> If RC = 'R', the number of columns in the matrices U and V,
  77. *> and if RC = 'C', the number of rows in U and V. If N = 0
  78. *> DORT03 does nothing. N must be at least zero.
  79. *> \endverbatim
  80. *>
  81. *> \param[in] K
  82. *> \verbatim
  83. *> K is INTEGER
  84. *> The number of rows or columns of U and V to compare.
  85. *> 0 <= K <= max(MU,MV).
  86. *> \endverbatim
  87. *>
  88. *> \param[in] U
  89. *> \verbatim
  90. *> U is DOUBLE PRECISION array, dimension (LDU,N)
  91. *> The first matrix to compare. If RC = 'R', U is MU by N, and
  92. *> if RC = 'C', U is N by MU.
  93. *> \endverbatim
  94. *>
  95. *> \param[in] LDU
  96. *> \verbatim
  97. *> LDU is INTEGER
  98. *> The leading dimension of U. If RC = 'R', LDU >= max(1,MU),
  99. *> and if RC = 'C', LDU >= max(1,N).
  100. *> \endverbatim
  101. *>
  102. *> \param[in] V
  103. *> \verbatim
  104. *> V is DOUBLE PRECISION array, dimension (LDV,N)
  105. *> The second matrix to compare. If RC = 'R', V is MV by N, and
  106. *> if RC = 'C', V is N by MV.
  107. *> \endverbatim
  108. *>
  109. *> \param[in] LDV
  110. *> \verbatim
  111. *> LDV is INTEGER
  112. *> The leading dimension of V. If RC = 'R', LDV >= max(1,MV),
  113. *> and if RC = 'C', LDV >= max(1,N).
  114. *> \endverbatim
  115. *>
  116. *> \param[out] WORK
  117. *> \verbatim
  118. *> WORK is DOUBLE PRECISION array, dimension (LWORK)
  119. *> \endverbatim
  120. *>
  121. *> \param[in] LWORK
  122. *> \verbatim
  123. *> LWORK is INTEGER
  124. *> The length of the array WORK. For best performance, LWORK
  125. *> should be at least N*N if RC = 'C' or M*M if RC = 'R', but
  126. *> the tests will be done even if LWORK is 0.
  127. *> \endverbatim
  128. *>
  129. *> \param[out] RESULT
  130. *> \verbatim
  131. *> RESULT is DOUBLE PRECISION
  132. *> The value computed by the test described above. RESULT is
  133. *> limited to 1/ulp to avoid overflow.
  134. *> \endverbatim
  135. *>
  136. *> \param[out] INFO
  137. *> \verbatim
  138. *> INFO is INTEGER
  139. *> 0 indicates a successful exit
  140. *> -k indicates the k-th parameter had an illegal value
  141. *> \endverbatim
  142. *
  143. * Authors:
  144. * ========
  145. *
  146. *> \author Univ. of Tennessee
  147. *> \author Univ. of California Berkeley
  148. *> \author Univ. of Colorado Denver
  149. *> \author NAG Ltd.
  150. *
  151. *> \ingroup double_eig
  152. *
  153. * =====================================================================
  154. SUBROUTINE DORT03( RC, MU, MV, N, K, U, LDU, V, LDV, WORK, LWORK,
  155. $ RESULT, INFO )
  156. *
  157. * -- LAPACK test routine --
  158. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  159. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  160. *
  161. * .. Scalar Arguments ..
  162. CHARACTER*( * ) RC
  163. INTEGER INFO, K, LDU, LDV, LWORK, MU, MV, N
  164. DOUBLE PRECISION RESULT
  165. * ..
  166. * .. Array Arguments ..
  167. DOUBLE PRECISION U( LDU, * ), V( LDV, * ), WORK( * )
  168. * ..
  169. *
  170. * =====================================================================
  171. *
  172. * .. Parameters ..
  173. DOUBLE PRECISION ZERO, ONE
  174. PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
  175. * ..
  176. * .. Local Scalars ..
  177. INTEGER I, IRC, J, LMX
  178. DOUBLE PRECISION RES1, RES2, S, ULP
  179. * ..
  180. * .. External Functions ..
  181. LOGICAL LSAME
  182. INTEGER IDAMAX
  183. DOUBLE PRECISION DLAMCH
  184. EXTERNAL LSAME, IDAMAX, DLAMCH
  185. * ..
  186. * .. Intrinsic Functions ..
  187. INTRINSIC ABS, DBLE, MAX, MIN, SIGN
  188. * ..
  189. * .. External Subroutines ..
  190. EXTERNAL DORT01, XERBLA
  191. * ..
  192. * .. Executable Statements ..
  193. *
  194. * Check inputs
  195. *
  196. INFO = 0
  197. IF( LSAME( RC, 'R' ) ) THEN
  198. IRC = 0
  199. ELSE IF( LSAME( RC, 'C' ) ) THEN
  200. IRC = 1
  201. ELSE
  202. IRC = -1
  203. END IF
  204. IF( IRC.EQ.-1 ) THEN
  205. INFO = -1
  206. ELSE IF( MU.LT.0 ) THEN
  207. INFO = -2
  208. ELSE IF( MV.LT.0 ) THEN
  209. INFO = -3
  210. ELSE IF( N.LT.0 ) THEN
  211. INFO = -4
  212. ELSE IF( K.LT.0 .OR. K.GT.MAX( MU, MV ) ) THEN
  213. INFO = -5
  214. ELSE IF( ( IRC.EQ.0 .AND. LDU.LT.MAX( 1, MU ) ) .OR.
  215. $ ( IRC.EQ.1 .AND. LDU.LT.MAX( 1, N ) ) ) THEN
  216. INFO = -7
  217. ELSE IF( ( IRC.EQ.0 .AND. LDV.LT.MAX( 1, MV ) ) .OR.
  218. $ ( IRC.EQ.1 .AND. LDV.LT.MAX( 1, N ) ) ) THEN
  219. INFO = -9
  220. END IF
  221. IF( INFO.NE.0 ) THEN
  222. CALL XERBLA( 'DORT03', -INFO )
  223. RETURN
  224. END IF
  225. *
  226. * Initialize result
  227. *
  228. RESULT = ZERO
  229. IF( MU.EQ.0 .OR. MV.EQ.0 .OR. N.EQ.0 )
  230. $ RETURN
  231. *
  232. * Machine constants
  233. *
  234. ULP = DLAMCH( 'Precision' )
  235. *
  236. IF( IRC.EQ.0 ) THEN
  237. *
  238. * Compare rows
  239. *
  240. RES1 = ZERO
  241. DO 20 I = 1, K
  242. LMX = IDAMAX( N, U( I, 1 ), LDU )
  243. S = SIGN( ONE, U( I, LMX ) )*SIGN( ONE, V( I, LMX ) )
  244. DO 10 J = 1, N
  245. RES1 = MAX( RES1, ABS( U( I, J )-S*V( I, J ) ) )
  246. 10 CONTINUE
  247. 20 CONTINUE
  248. RES1 = RES1 / ( DBLE( N )*ULP )
  249. *
  250. * Compute orthogonality of rows of V.
  251. *
  252. CALL DORT01( 'Rows', MV, N, V, LDV, WORK, LWORK, RES2 )
  253. *
  254. ELSE
  255. *
  256. * Compare columns
  257. *
  258. RES1 = ZERO
  259. DO 40 I = 1, K
  260. LMX = IDAMAX( N, U( 1, I ), 1 )
  261. S = SIGN( ONE, U( LMX, I ) )*SIGN( ONE, V( LMX, I ) )
  262. DO 30 J = 1, N
  263. RES1 = MAX( RES1, ABS( U( J, I )-S*V( J, I ) ) )
  264. 30 CONTINUE
  265. 40 CONTINUE
  266. RES1 = RES1 / ( DBLE( N )*ULP )
  267. *
  268. * Compute orthogonality of columns of V.
  269. *
  270. CALL DORT01( 'Columns', N, MV, V, LDV, WORK, LWORK, RES2 )
  271. END IF
  272. *
  273. RESULT = MIN( MAX( RES1, RES2 ), ONE / ULP )
  274. RETURN
  275. *
  276. * End of DORT03
  277. *
  278. END