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.

zglmts.f 6.0 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231
  1. *> \brief \b ZGLMTS
  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 ZGLMTS( N, M, P, A, AF, LDA, B, BF, LDB, D, DF, X, U,
  12. * WORK, LWORK, RWORK, RESULT )
  13. *
  14. * .. Scalar Arguments ..
  15. * INTEGER LDA, LDB, LWORK, M, N, P
  16. * DOUBLE PRECISION RESULT
  17. * ..
  18. * .. Array Arguments ..
  19. *
  20. *
  21. *> \par Purpose:
  22. * =============
  23. *>
  24. *> \verbatim
  25. *>
  26. *> ZGLMTS tests ZGGGLM - a subroutine for solving the generalized
  27. *> linear model problem.
  28. *> \endverbatim
  29. *
  30. * Arguments:
  31. * ==========
  32. *
  33. *> \param[in] N
  34. *> \verbatim
  35. *> N is INTEGER
  36. *> The number of rows of the matrices A and B. N >= 0.
  37. *> \endverbatim
  38. *>
  39. *> \param[in] M
  40. *> \verbatim
  41. *> M is INTEGER
  42. *> The number of columns of the matrix A. M >= 0.
  43. *> \endverbatim
  44. *>
  45. *> \param[in] P
  46. *> \verbatim
  47. *> P is INTEGER
  48. *> The number of columns of the matrix B. P >= 0.
  49. *> \endverbatim
  50. *>
  51. *> \param[in] A
  52. *> \verbatim
  53. *> A is COMPLEX*16 array, dimension (LDA,M)
  54. *> The N-by-M matrix A.
  55. *> \endverbatim
  56. *>
  57. *> \param[out] AF
  58. *> \verbatim
  59. *> AF is COMPLEX*16 array, dimension (LDA,M)
  60. *> \endverbatim
  61. *>
  62. *> \param[in] LDA
  63. *> \verbatim
  64. *> LDA is INTEGER
  65. *> The leading dimension of the arrays A, AF. LDA >= max(M,N).
  66. *> \endverbatim
  67. *>
  68. *> \param[in] B
  69. *> \verbatim
  70. *> B is COMPLEX*16 array, dimension (LDB,P)
  71. *> The N-by-P matrix A.
  72. *> \endverbatim
  73. *>
  74. *> \param[out] BF
  75. *> \verbatim
  76. *> BF is COMPLEX*16 array, dimension (LDB,P)
  77. *> \endverbatim
  78. *>
  79. *> \param[in] LDB
  80. *> \verbatim
  81. *> LDB is INTEGER
  82. *> The leading dimension of the arrays B, BF. LDB >= max(P,N).
  83. *> \endverbatim
  84. *>
  85. *> \param[in] D
  86. *> \verbatim
  87. *> D is COMPLEX*16 array, dimension( N )
  88. *> On input, the left hand side of the GLM.
  89. *> \endverbatim
  90. *>
  91. *> \param[out] DF
  92. *> \verbatim
  93. *> DF is COMPLEX*16 array, dimension( N )
  94. *> \endverbatim
  95. *>
  96. *> \param[out] X
  97. *> \verbatim
  98. *> X is COMPLEX*16 array, dimension( M )
  99. *> solution vector X in the GLM problem.
  100. *> \endverbatim
  101. *>
  102. *> \param[out] U
  103. *> \verbatim
  104. *> U is COMPLEX*16 array, dimension( P )
  105. *> solution vector U in the GLM problem.
  106. *> \endverbatim
  107. *>
  108. *> \param[out] WORK
  109. *> \verbatim
  110. *> WORK is COMPLEX*16 array, dimension (LWORK)
  111. *> \endverbatim
  112. *>
  113. *> \param[in] LWORK
  114. *> \verbatim
  115. *> LWORK is INTEGER
  116. *> The dimension of the array WORK.
  117. *> \endverbatim
  118. *>
  119. *> \param[out] RWORK
  120. *> \verbatim
  121. *> RWORK is DOUBLE PRECISION array, dimension (M)
  122. *> \endverbatim
  123. *>
  124. *> \param[out] RESULT
  125. *> \verbatim
  126. *> RESULT is DOUBLE PRECISION
  127. *> The test ratio:
  128. *> norm( d - A*x - B*u )
  129. *> RESULT = -----------------------------------------
  130. *> (norm(A)+norm(B))*(norm(x)+norm(u))*EPS
  131. *> \endverbatim
  132. *
  133. * Authors:
  134. * ========
  135. *
  136. *> \author Univ. of Tennessee
  137. *> \author Univ. of California Berkeley
  138. *> \author Univ. of Colorado Denver
  139. *> \author NAG Ltd.
  140. *
  141. *> \ingroup complex16_eig
  142. *
  143. * =====================================================================
  144. SUBROUTINE ZGLMTS( N, M, P, A, AF, LDA, B, BF, LDB, D, DF, X, U,
  145. $ WORK, LWORK, RWORK, RESULT )
  146. *
  147. * -- LAPACK test routine --
  148. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  149. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  150. *
  151. * .. Scalar Arguments ..
  152. INTEGER LDA, LDB, LWORK, M, N, P
  153. DOUBLE PRECISION RESULT
  154. * ..
  155. * .. Array Arguments ..
  156. *
  157. * ====================================================================
  158. *
  159. DOUBLE PRECISION RWORK( * )
  160. COMPLEX*16 A( LDA, * ), AF( LDA, * ), B( LDB, * ),
  161. $ BF( LDB, * ), D( * ), DF( * ), U( * ),
  162. $ WORK( LWORK ), X( * )
  163. * ..
  164. * .. Parameters ..
  165. DOUBLE PRECISION ZERO
  166. PARAMETER ( ZERO = 0.0D+0 )
  167. COMPLEX*16 CONE
  168. PARAMETER ( CONE = 1.0D+0 )
  169. * ..
  170. * .. Local Scalars ..
  171. INTEGER INFO
  172. DOUBLE PRECISION ANORM, BNORM, DNORM, EPS, UNFL, XNORM, YNORM
  173. * ..
  174. * .. External Functions ..
  175. DOUBLE PRECISION DLAMCH, DZASUM, ZLANGE
  176. EXTERNAL DLAMCH, DZASUM, ZLANGE
  177. * ..
  178. * .. External Subroutines ..
  179. *
  180. EXTERNAL ZCOPY, ZGEMV, ZGGGLM, ZLACPY
  181. * ..
  182. * .. Intrinsic Functions ..
  183. INTRINSIC MAX
  184. * ..
  185. * .. Executable Statements ..
  186. *
  187. EPS = DLAMCH( 'Epsilon' )
  188. UNFL = DLAMCH( 'Safe minimum' )
  189. ANORM = MAX( ZLANGE( '1', N, M, A, LDA, RWORK ), UNFL )
  190. BNORM = MAX( ZLANGE( '1', N, P, B, LDB, RWORK ), UNFL )
  191. *
  192. * Copy the matrices A and B to the arrays AF and BF,
  193. * and the vector D the array DF.
  194. *
  195. CALL ZLACPY( 'Full', N, M, A, LDA, AF, LDA )
  196. CALL ZLACPY( 'Full', N, P, B, LDB, BF, LDB )
  197. CALL ZCOPY( N, D, 1, DF, 1 )
  198. *
  199. * Solve GLM problem
  200. *
  201. CALL ZGGGLM( N, M, P, AF, LDA, BF, LDB, DF, X, U, WORK, LWORK,
  202. $ INFO )
  203. *
  204. * Test the residual for the solution of LSE
  205. *
  206. * norm( d - A*x - B*u )
  207. * RESULT = -----------------------------------------
  208. * (norm(A)+norm(B))*(norm(x)+norm(u))*EPS
  209. *
  210. CALL ZCOPY( N, D, 1, DF, 1 )
  211. CALL ZGEMV( 'No transpose', N, M, -CONE, A, LDA, X, 1, CONE, DF,
  212. $ 1 )
  213. *
  214. CALL ZGEMV( 'No transpose', N, P, -CONE, B, LDB, U, 1, CONE, DF,
  215. $ 1 )
  216. *
  217. DNORM = DZASUM( N, DF, 1 )
  218. XNORM = DZASUM( M, X, 1 ) + DZASUM( P, U, 1 )
  219. YNORM = ANORM + BNORM
  220. *
  221. IF( XNORM.LE.ZERO ) THEN
  222. RESULT = ZERO
  223. ELSE
  224. RESULT = ( ( DNORM / YNORM ) / XNORM ) / EPS
  225. END IF
  226. *
  227. RETURN
  228. *
  229. * End of ZGLMTS
  230. *
  231. END