Télécharger dorg2l.eso

Retour à la liste

Numérotation des lignes :

dorg2l
  1. C DORG2L SOURCE BP208322 22/09/16 21:15:04 11454
  2. *> \brief \b DORG2L generates all or part of the orthogonal matrix Q from a QL factorization determined by sgeqlf (unblocked algorithm).
  3. *
  4. * =========== DOCUMENTATION ===========
  5. *
  6. * Online html documentation available at
  7. * http://www.netlib.org/lapack/explore-html/
  8. *
  9. *> \htmlonly
  10. *> Download DORG2L + dependencies
  11. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dorg2l.f">
  12. *> [TGZ]</a>
  13. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dorg2l.f">
  14. *> [ZIP]</a>
  15. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorg2l.f">
  16. *> [TXT]</a>
  17. *> \endhtmlonly
  18. *
  19. * Definition:
  20. * ===========
  21. *
  22. * SUBROUTINE DORG2L( M, N, K, A, LDA, TAU, WORK, INFO )
  23. *
  24. * .. Scalar Arguments ..
  25. * INTEGER INFO, K, LDA, M, N
  26. * ..
  27. * .. Array Arguments ..
  28. * REAL*8 A( LDA, * ), TAU( * ), WORK( * )
  29. * ..
  30. *
  31. *
  32. *> \par Purpose:
  33. * =============
  34. *>
  35. *> \verbatim
  36. *>
  37. *> DORG2L generates an m by n real matrix Q with orthonormal columns,
  38. *> which is defined as the last n columns of a product of k elementary
  39. *> reflectors of order m
  40. *>
  41. *> Q = H(k) . . . H(2) H(1)
  42. *>
  43. *> as returned by DGEQLF.
  44. *> \endverbatim
  45. *
  46. * Arguments:
  47. * ==========
  48. *
  49. *> \param[in] M
  50. *> \verbatim
  51. *> M is INTEGER
  52. *> The number of rows of the matrix Q. M >= 0.
  53. *> \endverbatim
  54. *>
  55. *> \param[in] N
  56. *> \verbatim
  57. *> N is INTEGER
  58. *> The number of columns of the matrix Q. M >= N >= 0.
  59. *> \endverbatim
  60. *>
  61. *> \param[in] K
  62. *> \verbatim
  63. *> K is INTEGER
  64. *> The number of elementary reflectors whose product defines the
  65. *> matrix Q. N >= K >= 0.
  66. *> \endverbatim
  67. *>
  68. *> \param[in,out] A
  69. *> \verbatim
  70. *> A is REAL*8 array, dimension (LDA,N)
  71. *> On entry, the (n-k+i)-th column must contain the vector which
  72. *> defines the elementary reflector H(i), for i = 1,2,...,k, as
  73. *> returned by DGEQLF in the last k columns of its array
  74. *> argument A.
  75. *> On exit, the m by n matrix Q.
  76. *> \endverbatim
  77. *>
  78. *> \param[in] LDA
  79. *> \verbatim
  80. *> LDA is INTEGER
  81. *> The first dimension of the array A. LDA >= max(1,M).
  82. *> \endverbatim
  83. *>
  84. *> \param[in] TAU
  85. *> \verbatim
  86. *> TAU is REAL*8 array, dimension (K)
  87. *> TAU(i) must contain the scalar factor of the elementary
  88. *> reflector H(i), as returned by DGEQLF.
  89. *> \endverbatim
  90. *>
  91. *> \param[out] WORK
  92. *> \verbatim
  93. *> WORK is REAL*8 array, dimension (N)
  94. *> \endverbatim
  95. *>
  96. *> \param[out] INFO
  97. *> \verbatim
  98. *> INFO is INTEGER
  99. *> = 0: successful exit
  100. *> < 0: if INFO = -i, the i-th argument has an illegal value
  101. *> \endverbatim
  102. *
  103. * Authors:
  104. * ========
  105. *
  106. *> \author Univ. of Tennessee
  107. *> \author Univ. of California Berkeley
  108. *> \author Univ. of Colorado Denver
  109. *> \author NAG Ltd.
  110. *
  111. *> \ingroup doubleOTHERcomputational
  112. *
  113. * =====================================================================
  114. SUBROUTINE DORG2L( M, N, K, A, LDA, TAU, WORK, INFO )
  115. *
  116. * -- LAPACK computational routine --
  117. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  118. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  119. *
  120. * .. Scalar Arguments ..
  121. INTEGER INFO, K, LDA, M, N
  122. * ..
  123. * .. Array Arguments ..
  124. REAL*8 A( LDA, * ), TAU( * ), WORK( * )
  125. * ..
  126. *
  127. * =====================================================================
  128. *
  129. * .. Parameters ..
  130. REAL*8 ONE, ZERO
  131. PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
  132. * ..
  133. * .. Local Scalars ..
  134. INTEGER I, II, J, L
  135. * ..
  136. * .. External Subroutines ..
  137. EXTERNAL DLARF, DSCAL, XERBLA
  138. * ..
  139. * .. Intrinsic Functions ..
  140. * INTRINSIC MAX
  141. * ..
  142. * .. Executable Statements ..
  143. *
  144. * Test the input arguments
  145. *
  146. INFO = 0
  147. IF( M.LT.0 ) THEN
  148. INFO = -1
  149. ELSE IF( N.LT.0 .OR. N.GT.M ) THEN
  150. INFO = -2
  151. ELSE IF( K.LT.0 .OR. K.GT.N ) THEN
  152. INFO = -3
  153. ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
  154. INFO = -5
  155. END IF
  156. IF( INFO.NE.0 ) THEN
  157. CALL XERBLA( 'DORG2L', -INFO )
  158. RETURN
  159. END IF
  160. *
  161. * Quick return if possible
  162. *
  163. IF( N.LE.0 )
  164. $ RETURN
  165. *
  166. * Initialise columns 1:n-k to columns of the unit matrix
  167. *
  168. DO 20 J = 1, N - K
  169. DO 10 L = 1, M
  170. A( L, J ) = ZERO
  171. 10 CONTINUE
  172. A( M-N+J, J ) = ONE
  173. 20 CONTINUE
  174. *
  175. DO 40 I = 1, K
  176. II = N - K + I
  177. *
  178. * Apply H(i) to A(1:m-k+i,1:n-k+i) from the left
  179. *
  180. A( M-N+II, II ) = ONE
  181. CALL DLARF( 'Left', M-N+II, II-1, A( 1, II ), 1, TAU( I ), A,
  182. $ LDA, WORK )
  183. CALL DSCAL( M-N+II-1, -TAU( I ), A( 1, II ), 1 )
  184. A( M-N+II, II ) = ONE - TAU( I )
  185. *
  186. * Set A(m-k+i+1:m,n-k+i) to zero
  187. *
  188. DO 30 L = M - N + II + 1, M
  189. A( L, II ) = ZERO
  190. 30 CONTINUE
  191. 40 CONTINUE
  192. RETURN
  193. *
  194. * End of DORG2L
  195. *
  196. END
  197.  
  198.  

© Cast3M 2003 - Tous droits réservés.
Mentions légales