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.

zgedmd.f90 48 kB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148
  1. !> \brief \b ZGEDMD computes the Dynamic Mode Decomposition (DMD) for a pair of data snapshot matrices.
  2. !
  3. ! =========== DOCUMENTATION ===========
  4. !
  5. ! Definition:
  6. ! ===========
  7. !
  8. ! SUBROUTINE ZGEDMD( JOBS, JOBZ, JOBR, JOBF, WHTSVD, &
  9. ! M, N, X, LDX, Y, LDY, NRNK, TOL, &
  10. ! K, EIGS, Z, LDZ, RES, B, LDB, &
  11. ! W, LDW, S, LDS, ZWORK, LZWORK, &
  12. ! RWORK, LRWORK, IWORK, LIWORK, INFO )
  13. !......
  14. ! USE iso_fortran_env
  15. ! IMPLICIT NONE
  16. ! INTEGER, PARAMETER :: WP = real64
  17. !
  18. !......
  19. ! Scalar arguments
  20. ! CHARACTER, INTENT(IN) :: JOBS, JOBZ, JOBR, JOBF
  21. ! INTEGER, INTENT(IN) :: WHTSVD, M, N, LDX, LDY, &
  22. ! NRNK, LDZ, LDB, LDW, LDS, &
  23. ! LIWORK, LRWORK, LZWORK
  24. ! INTEGER, INTENT(OUT) :: K, INFO
  25. ! REAL(KIND=WP), INTENT(IN) :: TOL
  26. ! Array arguments
  27. ! COMPLEX(KIND=WP), INTENT(INOUT) :: X(LDX,*), Y(LDY,*)
  28. ! COMPLEX(KIND=WP), INTENT(OUT) :: Z(LDZ,*), B(LDB,*), &
  29. ! W(LDW,*), S(LDS,*)
  30. ! COMPLEX(KIND=WP), INTENT(OUT) :: EIGS(*)
  31. ! COMPLEX(KIND=WP), INTENT(OUT) :: ZWORK(*)
  32. ! REAL(KIND=WP), INTENT(OUT) :: RES(*)
  33. ! REAL(KIND=WP), INTENT(OUT) :: RWORK(*)
  34. ! INTEGER, INTENT(OUT) :: IWORK(*)
  35. !
  36. !............................................................
  37. !> \par Purpose:
  38. ! =============
  39. !> \verbatim
  40. !> ZGEDMD computes the Dynamic Mode Decomposition (DMD) for
  41. !> a pair of data snapshot matrices. For the input matrices
  42. !> X and Y such that Y = A*X with an unaccessible matrix
  43. !> A, ZGEDMD computes a certain number of Ritz pairs of A using
  44. !> the standard Rayleigh-Ritz extraction from a subspace of
  45. !> range(X) that is determined using the leading left singular
  46. !> vectors of X. Optionally, ZGEDMD returns the residuals
  47. !> of the computed Ritz pairs, the information needed for
  48. !> a refinement of the Ritz vectors, or the eigenvectors of
  49. !> the Exact DMD.
  50. !> For further details see the references listed
  51. !> below. For more details of the implementation see [3].
  52. !> \endverbatim
  53. !............................................................
  54. !> \par References:
  55. ! ================
  56. !> \verbatim
  57. !> [1] P. Schmid: Dynamic mode decomposition of numerical
  58. !> and experimental data,
  59. !> Journal of Fluid Mechanics 656, 5-28, 2010.
  60. !> [2] Z. Drmac, I. Mezic, R. Mohr: Data driven modal
  61. !> decompositions: analysis and enhancements,
  62. !> SIAM J. on Sci. Comp. 40 (4), A2253-A2285, 2018.
  63. !> [3] Z. Drmac: A LAPACK implementation of the Dynamic
  64. !> Mode Decomposition I. Technical report. AIMDyn Inc.
  65. !> and LAPACK Working Note 298.
  66. !> [4] J. Tu, C. W. Rowley, D. M. Luchtenburg, S. L.
  67. !> Brunton, N. Kutz: On Dynamic Mode Decomposition:
  68. !> Theory and Applications, Journal of Computational
  69. !> Dynamics 1(2), 391 -421, 2014.
  70. !> \endverbatim
  71. !......................................................................
  72. !> \par Developed and supported by:
  73. ! ================================
  74. !> \verbatim
  75. !> Developed and coded by Zlatko Drmac, Faculty of Science,
  76. !> University of Zagreb; drmac@math.hr
  77. !> In cooperation with
  78. !> AIMdyn Inc., Santa Barbara, CA.
  79. !> and supported by
  80. !> - DARPA SBIR project "Koopman Operator-Based Forecasting
  81. !> for Nonstationary Processes from Near-Term, Limited
  82. !> Observational Data" Contract No: W31P4Q-21-C-0007
  83. !> - DARPA PAI project "Physics-Informed Machine Learning
  84. !> Methodologies" Contract No: HR0011-18-9-0033
  85. !> - DARPA MoDyL project "A Data-Driven, Operator-Theoretic
  86. !> Framework for Space-Time Analysis of Process Dynamics"
  87. !> Contract No: HR0011-16-C-0116
  88. !> Any opinions, findings and conclusions or recommendations
  89. !> expressed in this material are those of the author and
  90. !> do not necessarily reflect the views of the DARPA SBIR
  91. !> Program Office
  92. !> \endverbatim
  93. !......................................................................
  94. !> \par Distribution Statement A:
  95. ! ==============================
  96. !> \verbatim
  97. !> Approved for Public Release, Distribution Unlimited.
  98. !> Cleared by DARPA on September 29, 2022
  99. !> \endverbatim
  100. !............................................................
  101. ! Arguments
  102. ! =========
  103. !
  104. !> \param[in] JOBS
  105. !> \verbatim
  106. !> JOBS (input) CHARACTER*1
  107. !> Determines whether the initial data snapshots are scaled
  108. !> by a diagonal matrix.
  109. !> 'S' :: The data snapshots matrices X and Y are multiplied
  110. !> with a diagonal matrix D so that X*D has unit
  111. !> nonzero columns (in the Euclidean 2-norm)
  112. !> 'C' :: The snapshots are scaled as with the 'S' option.
  113. !> If it is found that an i-th column of X is zero
  114. !> vector and the corresponding i-th column of Y is
  115. !> non-zero, then the i-th column of Y is set to
  116. !> zero and a warning flag is raised.
  117. !> 'Y' :: The data snapshots matrices X and Y are multiplied
  118. !> by a diagonal matrix D so that Y*D has unit
  119. !> nonzero columns (in the Euclidean 2-norm)
  120. !> 'N' :: No data scaling.
  121. !> \endverbatim
  122. !.....
  123. !> \param[in] JOBZ
  124. !> \verbatim
  125. !> JOBZ (input) CHARACTER*1
  126. !> Determines whether the eigenvectors (Koopman modes) will
  127. !> be computed.
  128. !> 'V' :: The eigenvectors (Koopman modes) will be computed
  129. !> and returned in the matrix Z.
  130. !> See the description of Z.
  131. !> 'F' :: The eigenvectors (Koopman modes) will be returned
  132. !> in factored form as the product X(:,1:K)*W, where X
  133. !> contains a POD basis (leading left singular vectors
  134. !> of the data matrix X) and W contains the eigenvectors
  135. !> of the corresponding Rayleigh quotient.
  136. !> See the descriptions of K, X, W, Z.
  137. !> 'N' :: The eigenvectors are not computed.
  138. !> \endverbatim
  139. !.....
  140. !> \param[in] JOBR
  141. !> \verbatim
  142. !> JOBR (input) CHARACTER*1
  143. !> Determines whether to compute the residuals.
  144. !> 'R' :: The residuals for the computed eigenpairs will be
  145. !> computed and stored in the array RES.
  146. !> See the description of RES.
  147. !> For this option to be legal, JOBZ must be 'V'.
  148. !> 'N' :: The residuals are not computed.
  149. !> \endverbatim
  150. !.....
  151. !> \param[in] JOBF
  152. !> \verbatim
  153. !> JOBF (input) CHARACTER*1
  154. !> Specifies whether to store information needed for post-
  155. !> processing (e.g. computing refined Ritz vectors)
  156. !> 'R' :: The matrix needed for the refinement of the Ritz
  157. !> vectors is computed and stored in the array B.
  158. !> See the description of B.
  159. !> 'E' :: The unscaled eigenvectors of the Exact DMD are
  160. !> computed and returned in the array B. See the
  161. !> description of B.
  162. !> 'N' :: No eigenvector refinement data is computed.
  163. !> \endverbatim
  164. !.....
  165. !> \param[in] WHTSVD
  166. !> \verbatim
  167. !> WHTSVD (input) INTEGER, WHSTVD in { 1, 2, 3, 4 }
  168. !> Allows for a selection of the SVD algorithm from the
  169. !> LAPACK library.
  170. !> 1 :: ZGESVD (the QR SVD algorithm)
  171. !> 2 :: ZGESDD (the Divide and Conquer algorithm; if enough
  172. !> workspace available, this is the fastest option)
  173. !> 3 :: ZGESVDQ (the preconditioned QR SVD ; this and 4
  174. !> are the most accurate options)
  175. !> 4 :: ZGEJSV (the preconditioned Jacobi SVD; this and 3
  176. !> are the most accurate options)
  177. !> For the four methods above, a significant difference in
  178. !> the accuracy of small singular values is possible if
  179. !> the snapshots vary in norm so that X is severely
  180. !> ill-conditioned. If small (smaller than EPS*||X||)
  181. !> singular values are of interest and JOBS=='N', then
  182. !> the options (3, 4) give the most accurate results, where
  183. !> the option 4 is slightly better and with stronger
  184. !> theoretical background.
  185. !> If JOBS=='S', i.e. the columns of X will be normalized,
  186. !> then all methods give nearly equally accurate results.
  187. !> \endverbatim
  188. !.....
  189. !> \param[in] M
  190. !> \verbatim
  191. !> M (input) INTEGER, M>= 0
  192. !> The state space dimension (the row dimension of X, Y).
  193. !> \endverbatim
  194. !.....
  195. !> \param[in] N
  196. !> \verbatim
  197. !> N (input) INTEGER, 0 <= N <= M
  198. !> The number of data snapshot pairs
  199. !> (the number of columns of X and Y).
  200. !> \endverbatim
  201. !.....
  202. !> \param[in] LDX
  203. !> \verbatim
  204. !> X (input/output) COMPLEX(KIND=WP) M-by-N array
  205. !> > On entry, X contains the data snapshot matrix X. It is
  206. !> assumed that the column norms of X are in the range of
  207. !> the normalized floating point numbers.
  208. !> < On exit, the leading K columns of X contain a POD basis,
  209. !> i.e. the leading K left singular vectors of the input
  210. !> data matrix X, U(:,1:K). All N columns of X contain all
  211. !> left singular vectors of the input matrix X.
  212. !> See the descriptions of K, Z and W.
  213. !.....
  214. !> LDX (input) INTEGER, LDX >= M
  215. !> The leading dimension of the array X.
  216. !> \endverbatim
  217. !.....
  218. !> \param[in,out] Y
  219. !> \verbatim
  220. !> Y (input/workspace/output) COMPLEX(KIND=WP) M-by-N array
  221. !> > On entry, Y contains the data snapshot matrix Y
  222. !> < On exit,
  223. !> If JOBR == 'R', the leading K columns of Y contain
  224. !> the residual vectors for the computed Ritz pairs.
  225. !> See the description of RES.
  226. !> If JOBR == 'N', Y contains the original input data,
  227. !> scaled according to the value of JOBS.
  228. !> \endverbatim
  229. !.....
  230. !> \param[in] LDY
  231. !> \verbatim
  232. !> LDY (input) INTEGER , LDY >= M
  233. !> The leading dimension of the array Y.
  234. !> \endverbatim
  235. !.....
  236. !> \param[in] NRNK
  237. !> \verbatim
  238. !> NRNK (input) INTEGER
  239. !> Determines the mode how to compute the numerical rank,
  240. !> i.e. how to truncate small singular values of the input
  241. !> matrix X. On input, if
  242. !> NRNK = -1 :: i-th singular value sigma(i) is truncated
  243. !> if sigma(i) <= TOL*sigma(1)
  244. !> This option is recommended.
  245. !> NRNK = -2 :: i-th singular value sigma(i) is truncated
  246. !> if sigma(i) <= TOL*sigma(i-1)
  247. !> This option is included for R&D purposes.
  248. !> It requires highly accurate SVD, which
  249. !> may not be feasible.
  250. !> The numerical rank can be enforced by using positive
  251. !> value of NRNK as follows:
  252. !> 0 < NRNK <= N :: at most NRNK largest singular values
  253. !> will be used. If the number of the computed nonzero
  254. !> singular values is less than NRNK, then only those
  255. !> nonzero values will be used and the actually used
  256. !> dimension is less than NRNK. The actual number of
  257. !> the nonzero singular values is returned in the variable
  258. !> K. See the descriptions of TOL and K.
  259. !> \endverbatim
  260. !.....
  261. !> \param[in] TOL
  262. !> \verbatim
  263. !> TOL (input) REAL(KIND=WP), 0 <= TOL < 1
  264. !> The tolerance for truncating small singular values.
  265. !> See the description of NRNK.
  266. !> \endverbatim
  267. !.....
  268. !> \param[out] K
  269. !> \verbatim
  270. !> K (output) INTEGER, 0 <= K <= N
  271. !> The dimension of the POD basis for the data snapshot
  272. !> matrix X and the number of the computed Ritz pairs.
  273. !> The value of K is determined according to the rule set
  274. !> by the parameters NRNK and TOL.
  275. !> See the descriptions of NRNK and TOL.
  276. !> \endverbatim
  277. !.....
  278. !> \param[out] EIGS
  279. !> \verbatim
  280. !> EIGS (output) COMPLEX(KIND=WP) N-by-1 array
  281. !> The leading K (K<=N) entries of EIGS contain
  282. !> the computed eigenvalues (Ritz values).
  283. !> See the descriptions of K, and Z.
  284. !> \endverbatim
  285. !.....
  286. !> \param[out] Z
  287. !> \verbatim
  288. !> Z (workspace/output) COMPLEX(KIND=WP) M-by-N array
  289. !> If JOBZ =='V' then Z contains the Ritz vectors. Z(:,i)
  290. !> is an eigenvector of the i-th Ritz value; ||Z(:,i)||_2=1.
  291. !> If JOBZ == 'F', then the Z(:,i)'s are given implicitly as
  292. !> the columns of X(:,1:K)*W(1:K,1:K), i.e. X(:,1:K)*W(:,i)
  293. !> is an eigenvector corresponding to EIGS(i). The columns
  294. !> of W(1:k,1:K) are the computed eigenvectors of the
  295. !> K-by-K Rayleigh quotient.
  296. !> See the descriptions of EIGS, X and W.
  297. !> \endverbatim
  298. !.....
  299. !> \param[in] LDZ
  300. !> \verbatim
  301. !> LDZ (input) INTEGER , LDZ >= M
  302. !> The leading dimension of the array Z.
  303. !> \endverbatim
  304. !.....
  305. !> \param[out] RES
  306. !> \verbatim
  307. !> RES (output) REAL(KIND=WP) N-by-1 array
  308. !> RES(1:K) contains the residuals for the K computed
  309. !> Ritz pairs,
  310. !> RES(i) = || A * Z(:,i) - EIGS(i)*Z(:,i))||_2.
  311. !> See the description of EIGS and Z.
  312. !> \endverbatim
  313. !.....
  314. !> \param[out] B
  315. !> \verbatim
  316. !> B (output) COMPLEX(KIND=WP) M-by-N array.
  317. !> IF JOBF =='R', B(1:M,1:K) contains A*U(:,1:K), and can
  318. !> be used for computing the refined vectors; see further
  319. !> details in the provided references.
  320. !> If JOBF == 'E', B(1:M,1:K) contains
  321. !> A*U(:,1:K)*W(1:K,1:K), which are the vectors from the
  322. !> Exact DMD, up to scaling by the inverse eigenvalues.
  323. !> If JOBF =='N', then B is not referenced.
  324. !> See the descriptions of X, W, K.
  325. !> \endverbatim
  326. !.....
  327. !> \param[in] LDB
  328. !> \verbatim
  329. !> LDB (input) INTEGER, LDB >= M
  330. !> The leading dimension of the array B.
  331. !> \endverbatim
  332. !.....
  333. !> \param[out] W
  334. !> \verbatim
  335. !> W (workspace/output) COMPLEX(KIND=WP) N-by-N array
  336. !> On exit, W(1:K,1:K) contains the K computed
  337. !> eigenvectors of the matrix Rayleigh quotient.
  338. !> The Ritz vectors (returned in Z) are the
  339. !> product of X (containing a POD basis for the input
  340. !> matrix X) and W. See the descriptions of K, S, X and Z.
  341. !> W is also used as a workspace to temporarily store the
  342. !> right singular vectors of X.
  343. !> \endverbatim
  344. !.....
  345. !> \param[in] LDW
  346. !> \verbatim
  347. !> LDW (input) INTEGER, LDW >= N
  348. !> The leading dimension of the array W.
  349. !> \endverbatim
  350. !.....
  351. !> \param[out] S
  352. !> \verbatim
  353. !> S (workspace/output) COMPLEX(KIND=WP) N-by-N array
  354. !> The array S(1:K,1:K) is used for the matrix Rayleigh
  355. !> quotient. This content is overwritten during
  356. !> the eigenvalue decomposition by ZGEEV.
  357. !> See the description of K.
  358. !> \endverbatim
  359. !.....
  360. !> \param[in] LDS
  361. !> \verbatim
  362. !> LDS (input) INTEGER, LDS >= N
  363. !> The leading dimension of the array S.
  364. !> \endverbatim
  365. !.....
  366. !> \param[out] ZWORK
  367. !> \verbatim
  368. !> ZWORK (workspace/output) COMPLEX(KIND=WP) LZWORK-by-1 array
  369. !> ZWORK is used as complex workspace in the complex SVD, as
  370. !> specified by WHTSVD (1,2, 3 or 4) and for ZGEEV for computing
  371. !> the eigenvalues of a Rayleigh quotient.
  372. !> If the call to ZGEDMD is only workspace query, then
  373. !> ZWORK(1) contains the minimal complex workspace length and
  374. !> ZWORK(2) is the optimal complex workspace length.
  375. !> Hence, the length of work is at least 2.
  376. !> See the description of LZWORK.
  377. !> \endverbatim
  378. !.....
  379. !> \param[in] LZWORK
  380. !> \verbatim
  381. !> LZWORK (input) INTEGER
  382. !> The minimal length of the workspace vector ZWORK.
  383. !> LZWORK is calculated as MAX(LZWORK_SVD, LZWORK_ZGEEV),
  384. !> where LZWORK_ZGEEV = MAX( 1, 2*N ) and the minimal
  385. !> LZWORK_SVD is calculated as follows
  386. !> If WHTSVD == 1 :: ZGESVD ::
  387. !> LZWORK_SVD = MAX(1,2*MIN(M,N)+MAX(M,N))
  388. !> If WHTSVD == 2 :: ZGESDD ::
  389. !> LZWORK_SVD = 2*MIN(M,N)*MIN(M,N)+2*MIN(M,N)+MAX(M,N)
  390. !> If WHTSVD == 3 :: ZGESVDQ ::
  391. !> LZWORK_SVD = obtainable by a query
  392. !> If WHTSVD == 4 :: ZGEJSV ::
  393. !> LZWORK_SVD = obtainable by a query
  394. !> If on entry LZWORK = -1, then a workspace query is
  395. !> assumed and the procedure only computes the minimal
  396. !> and the optimal workspace lengths and returns them in
  397. !> LZWORK(1) and LZWORK(2), respectively.
  398. !> \endverbatim
  399. !.....
  400. !> \param[out] RWORK
  401. !> \verbatim
  402. !> RWORK (workspace/output) REAL(KIND=WP) LRWORK-by-1 array
  403. !> On exit, RWORK(1:N) contains the singular values of
  404. !> X (for JOBS=='N') or column scaled X (JOBS=='S', 'C').
  405. !> If WHTSVD==4, then RWORK(N+1) and RWORK(N+2) contain
  406. !> scaling factor RWORK(N+2)/RWORK(N+1) used to scale X
  407. !> and Y to avoid overflow in the SVD of X.
  408. !> This may be of interest if the scaling option is off
  409. !> and as many as possible smallest eigenvalues are
  410. !> desired to the highest feasible accuracy.
  411. !> If the call to ZGEDMD is only workspace query, then
  412. !> RWORK(1) contains the minimal workspace length.
  413. !> See the description of LRWORK.
  414. !> \endverbatim
  415. !.....
  416. !> \param[in] LRWORK
  417. !> \verbatim
  418. !> LRWORK (input) INTEGER
  419. !> The minimal length of the workspace vector RWORK.
  420. !> LRWORK is calculated as follows:
  421. !> LRWORK = MAX(1, N+LRWORK_SVD,N+LRWORK_ZGEEV), where
  422. !> LRWORK_ZGEEV = MAX(1,2*N) and RWORK_SVD is the real workspace
  423. !> for the SVD subroutine determined by the input parameter
  424. !> WHTSVD.
  425. !> If WHTSVD == 1 :: ZGESVD ::
  426. !> LRWORK_SVD = 5*MIN(M,N)
  427. !> If WHTSVD == 2 :: ZGESDD ::
  428. !> LRWORK_SVD = MAX(5*MIN(M,N)*MIN(M,N)+7*MIN(M,N),
  429. !> 2*MAX(M,N)*MIN(M,N)+2*MIN(M,N)*MIN(M,N)+MIN(M,N) ) )
  430. !> If WHTSVD == 3 :: ZGESVDQ ::
  431. !> LRWORK_SVD = obtainable by a query
  432. !> If WHTSVD == 4 :: ZGEJSV ::
  433. !> LRWORK_SVD = obtainable by a query
  434. !> If on entry LRWORK = -1, then a workspace query is
  435. !> assumed and the procedure only computes the minimal
  436. !> real workspace length and returns it in RWORK(1).
  437. !> \endverbatim
  438. !.....
  439. !> \param[out] IWORK
  440. !> \verbatim
  441. !> IWORK (workspace/output) INTEGER LIWORK-by-1 array
  442. !> Workspace that is required only if WHTSVD equals
  443. !> 2 , 3 or 4. (See the description of WHTSVD).
  444. !> If on entry LWORK =-1 or LIWORK=-1, then the
  445. !> minimal length of IWORK is computed and returned in
  446. !> IWORK(1). See the description of LIWORK.
  447. !> \endverbatim
  448. !.....
  449. !> \param[in] LIWORK
  450. !> \verbatim
  451. !> LIWORK (input) INTEGER
  452. !> The minimal length of the workspace vector IWORK.
  453. !> If WHTSVD == 1, then only IWORK(1) is used; LIWORK >=1
  454. !> If WHTSVD == 2, then LIWORK >= MAX(1,8*MIN(M,N))
  455. !> If WHTSVD == 3, then LIWORK >= MAX(1,M+N-1)
  456. !> If WHTSVD == 4, then LIWORK >= MAX(3,M+3*N)
  457. !> If on entry LIWORK = -1, then a workspace query is
  458. !> assumed and the procedure only computes the minimal
  459. !> and the optimal workspace lengths for ZWORK, RWORK and
  460. !> IWORK. See the descriptions of ZWORK, RWORK and IWORK.
  461. !> \endverbatim
  462. !.....
  463. !> \param[out] INFO
  464. !> \verbatim
  465. !> INFO (output) INTEGER
  466. !> -i < 0 :: On entry, the i-th argument had an
  467. !> illegal value
  468. !> = 0 :: Successful return.
  469. !> = 1 :: Void input. Quick exit (M=0 or N=0).
  470. !> = 2 :: The SVD computation of X did not converge.
  471. !> Suggestion: Check the input data and/or
  472. !> repeat with different WHTSVD.
  473. !> = 3 :: The computation of the eigenvalues did not
  474. !> converge.
  475. !> = 4 :: If data scaling was requested on input and
  476. !> the procedure found inconsistency in the data
  477. !> such that for some column index i,
  478. !> X(:,i) = 0 but Y(:,i) /= 0, then Y(:,i) is set
  479. !> to zero if JOBS=='C'. The computation proceeds
  480. !> with original or modified data and warning
  481. !> flag is set with INFO=4.
  482. !> \endverbatim
  483. !
  484. ! Authors:
  485. ! ========
  486. !
  487. !> \author Zlatko Drmac
  488. !
  489. !> \ingroup gedmd
  490. !
  491. !.............................................................
  492. !.............................................................
  493. SUBROUTINE ZGEDMD( JOBS, JOBZ, JOBR, JOBF, WHTSVD, &
  494. M, N, X, LDX, Y, LDY, NRNK, TOL, &
  495. K, EIGS, Z, LDZ, RES, B, LDB, &
  496. W, LDW, S, LDS, ZWORK, LZWORK, &
  497. RWORK, LRWORK, IWORK, LIWORK, INFO )
  498. !
  499. ! -- LAPACK driver routine --
  500. !
  501. ! -- LAPACK is a software package provided by University of --
  502. ! -- Tennessee, University of California Berkeley, University of --
  503. ! -- Colorado Denver and NAG Ltd.. --
  504. !
  505. !.....
  506. USE iso_fortran_env
  507. IMPLICIT NONE
  508. INTEGER, PARAMETER :: WP = real64
  509. !
  510. ! Scalar arguments
  511. ! ~~~~~~~~~~~~~~~~
  512. CHARACTER, INTENT(IN) :: JOBS, JOBZ, JOBR, JOBF
  513. INTEGER, INTENT(IN) :: WHTSVD, M, N, LDX, LDY, &
  514. NRNK, LDZ, LDB, LDW, LDS, &
  515. LIWORK, LRWORK, LZWORK
  516. INTEGER, INTENT(OUT) :: K, INFO
  517. REAL(KIND=WP), INTENT(IN) :: TOL
  518. !
  519. ! Array arguments
  520. ! ~~~~~~~~~~~~~~~
  521. COMPLEX(KIND=WP), INTENT(INOUT) :: X(LDX,*), Y(LDY,*)
  522. COMPLEX(KIND=WP), INTENT(OUT) :: Z(LDZ,*), B(LDB,*), &
  523. W(LDW,*), S(LDS,*)
  524. COMPLEX(KIND=WP), INTENT(OUT) :: EIGS(*)
  525. COMPLEX(KIND=WP), INTENT(OUT) :: ZWORK(*)
  526. REAL(KIND=WP), INTENT(OUT) :: RES(*)
  527. REAL(KIND=WP), INTENT(OUT) :: RWORK(*)
  528. INTEGER, INTENT(OUT) :: IWORK(*)
  529. !
  530. ! Parameters
  531. ! ~~~~~~~~~~
  532. REAL(KIND=WP), PARAMETER :: ONE = 1.0_WP
  533. REAL(KIND=WP), PARAMETER :: ZERO = 0.0_WP
  534. COMPLEX(KIND=WP), PARAMETER :: ZONE = ( 1.0_WP, 0.0_WP )
  535. COMPLEX(KIND=WP), PARAMETER :: ZZERO = ( 0.0_WP, 0.0_WP )
  536. !
  537. ! Local scalars
  538. ! ~~~~~~~~~~~~~
  539. REAL(KIND=WP) :: OFL, ROOTSC, SCALE, SMALL, &
  540. SSUM, XSCL1, XSCL2
  541. INTEGER :: i, j, IMINWR, INFO1, INFO2, &
  542. LWRKEV, LWRSDD, LWRSVD, LWRSVJ, &
  543. LWRSVQ, MLWORK, MWRKEV, MWRSDD, &
  544. MWRSVD, MWRSVJ, MWRSVQ, NUMRNK, &
  545. OLWORK, MLRWRK
  546. LOGICAL :: BADXY, LQUERY, SCCOLX, SCCOLY, &
  547. WNTEX, WNTREF, WNTRES, WNTVEC
  548. CHARACTER :: JOBZL, T_OR_N
  549. CHARACTER :: JSVOPT
  550. !
  551. ! Local arrays
  552. ! ~~~~~~~~~~~~
  553. REAL(KIND=WP) :: RDUMMY(2)
  554. !
  555. ! External functions (BLAS and LAPACK)
  556. ! ~~~~~~~~~~~~~~~~~
  557. REAL(KIND=WP) ZLANGE, DLAMCH, DZNRM2
  558. EXTERNAL ZLANGE, DLAMCH, DZNRM2, IZAMAX
  559. INTEGER IZAMAX
  560. LOGICAL DISNAN, LSAME
  561. EXTERNAL DISNAN, LSAME
  562. !
  563. ! External subroutines (BLAS and LAPACK)
  564. ! ~~~~~~~~~~~~~~~~~~~~
  565. EXTERNAL ZAXPY, ZGEMM, ZDSCAL
  566. EXTERNAL ZGEEV, ZGEJSV, ZGESDD, ZGESVD, ZGESVDQ, &
  567. ZLACPY, ZLASCL, ZLASSQ, XERBLA
  568. !
  569. ! Intrinsic functions
  570. ! ~~~~~~~~~~~~~~~~~~~
  571. INTRINSIC DBLE, INT, MAX, SQRT
  572. !............................................................
  573. !
  574. ! Test the input arguments
  575. !
  576. WNTRES = LSAME(JOBR,'R')
  577. SCCOLX = LSAME(JOBS,'S') .OR. LSAME(JOBS,'C')
  578. SCCOLY = LSAME(JOBS,'Y')
  579. WNTVEC = LSAME(JOBZ,'V')
  580. WNTREF = LSAME(JOBF,'R')
  581. WNTEX = LSAME(JOBF,'E')
  582. INFO = 0
  583. LQUERY = ( ( LZWORK == -1 ) .OR. ( LIWORK == -1 ) &
  584. .OR. ( LRWORK == -1 ) )
  585. !
  586. IF ( .NOT. (SCCOLX .OR. SCCOLY .OR. &
  587. LSAME(JOBS,'N')) ) THEN
  588. INFO = -1
  589. ELSE IF ( .NOT. (WNTVEC .OR. LSAME(JOBZ,'N') &
  590. .OR. LSAME(JOBZ,'F')) ) THEN
  591. INFO = -2
  592. ELSE IF ( .NOT. (WNTRES .OR. LSAME(JOBR,'N')) .OR. &
  593. ( WNTRES .AND. (.NOT.WNTVEC) ) ) THEN
  594. INFO = -3
  595. ELSE IF ( .NOT. (WNTREF .OR. WNTEX .OR. &
  596. LSAME(JOBF,'N') ) ) THEN
  597. INFO = -4
  598. ELSE IF ( .NOT.((WHTSVD == 1) .OR. (WHTSVD == 2) .OR. &
  599. (WHTSVD == 3) .OR. (WHTSVD == 4) )) THEN
  600. INFO = -5
  601. ELSE IF ( M < 0 ) THEN
  602. INFO = -6
  603. ELSE IF ( ( N < 0 ) .OR. ( N > M ) ) THEN
  604. INFO = -7
  605. ELSE IF ( LDX < M ) THEN
  606. INFO = -9
  607. ELSE IF ( LDY < M ) THEN
  608. INFO = -11
  609. ELSE IF ( .NOT. (( NRNK == -2).OR.(NRNK == -1).OR. &
  610. ((NRNK >= 1).AND.(NRNK <=N ))) ) THEN
  611. INFO = -12
  612. ELSE IF ( ( TOL < ZERO ) .OR. ( TOL >= ONE ) ) THEN
  613. INFO = -13
  614. ELSE IF ( LDZ < M ) THEN
  615. INFO = -17
  616. ELSE IF ( (WNTREF .OR. WNTEX ) .AND. ( LDB < M ) ) THEN
  617. INFO = -20
  618. ELSE IF ( LDW < N ) THEN
  619. INFO = -22
  620. ELSE IF ( LDS < N ) THEN
  621. INFO = -24
  622. END IF
  623. !
  624. IF ( INFO == 0 ) THEN
  625. ! Compute the minimal and the optimal workspace
  626. ! requirements. Simulate running the code and
  627. ! determine minimal and optimal sizes of the
  628. ! workspace at any moment of the run.
  629. IF ( N == 0 ) THEN
  630. ! Quick return. All output except K is void.
  631. ! INFO=1 signals the void input.
  632. ! In case of a workspace query, the default
  633. ! minimal workspace lengths are returned.
  634. IF ( LQUERY ) THEN
  635. IWORK(1) = 1
  636. RWORK(1) = 1
  637. ZWORK(1) = 2
  638. ZWORK(2) = 2
  639. ELSE
  640. K = 0
  641. END IF
  642. INFO = 1
  643. RETURN
  644. END IF
  645. IMINWR = 1
  646. MLRWRK = MAX(1,N)
  647. MLWORK = 2
  648. OLWORK = 2
  649. SELECT CASE ( WHTSVD )
  650. CASE (1)
  651. ! The following is specified as the minimal
  652. ! length of WORK in the definition of ZGESVD:
  653. ! MWRSVD = MAX(1,2*MIN(M,N)+MAX(M,N))
  654. MWRSVD = MAX(1,2*MIN(M,N)+MAX(M,N))
  655. MLWORK = MAX(MLWORK,MWRSVD)
  656. MLRWRK = MAX(MLRWRK,N + 5*MIN(M,N))
  657. IF ( LQUERY ) THEN
  658. CALL ZGESVD( 'O', 'S', M, N, X, LDX, RWORK, &
  659. B, LDB, W, LDW, ZWORK, -1, RDUMMY, INFO1 )
  660. LWRSVD = INT( ZWORK(1) )
  661. OLWORK = MAX(OLWORK,LWRSVD)
  662. END IF
  663. CASE (2)
  664. ! The following is specified as the minimal
  665. ! length of WORK in the definition of ZGESDD:
  666. ! MWRSDD = 2*min(M,N)*min(M,N)+2*min(M,N)+max(M,N).
  667. ! RWORK length: 5*MIN(M,N)*MIN(M,N)+7*MIN(M,N)
  668. ! In LAPACK 3.10.1 RWORK is defined differently.
  669. ! Below we take max over the two versions.
  670. ! IMINWR = 8*MIN(M,N)
  671. MWRSDD = 2*MIN(M,N)*MIN(M,N)+2*MIN(M,N)+MAX(M,N)
  672. MLWORK = MAX(MLWORK,MWRSDD)
  673. IMINWR = 8*MIN(M,N)
  674. MLRWRK = MAX( MLRWRK, N + &
  675. MAX( 5*MIN(M,N)*MIN(M,N)+7*MIN(M,N), &
  676. 5*MIN(M,N)*MIN(M,N)+5*MIN(M,N), &
  677. 2*MAX(M,N)*MIN(M,N)+ &
  678. 2*MIN(M,N)*MIN(M,N)+MIN(M,N) ) )
  679. IF ( LQUERY ) THEN
  680. CALL ZGESDD( 'O', M, N, X, LDX, RWORK, B,LDB,&
  681. W, LDW, ZWORK, -1, RDUMMY, IWORK, INFO1 )
  682. LWRSDD = MAX( MWRSDD,INT( ZWORK(1) ))
  683. ! Possible bug in ZGESDD optimal workspace size.
  684. OLWORK = MAX(OLWORK,LWRSDD)
  685. END IF
  686. CASE (3)
  687. CALL ZGESVDQ( 'H', 'P', 'N', 'R', 'R', M, N, &
  688. X, LDX, RWORK, Z, LDZ, W, LDW, NUMRNK, &
  689. IWORK, -1, ZWORK, -1, RDUMMY, -1, INFO1 )
  690. IMINWR = IWORK(1)
  691. MWRSVQ = INT(ZWORK(2))
  692. MLWORK = MAX(MLWORK,MWRSVQ)
  693. MLRWRK = MAX(MLRWRK,N + INT(RDUMMY(1)))
  694. IF ( LQUERY ) THEN
  695. LWRSVQ = INT(ZWORK(1))
  696. OLWORK = MAX(OLWORK,LWRSVQ)
  697. END IF
  698. CASE (4)
  699. JSVOPT = 'J'
  700. CALL ZGEJSV( 'F', 'U', JSVOPT, 'R', 'N', 'P', M, &
  701. N, X, LDX, RWORK, Z, LDZ, W, LDW, &
  702. ZWORK, -1, RDUMMY, -1, IWORK, INFO1 )
  703. IMINWR = IWORK(1)
  704. MWRSVJ = INT(ZWORK(2))
  705. MLWORK = MAX(MLWORK,MWRSVJ)
  706. MLRWRK = MAX(MLRWRK,N + MAX(7,INT(RDUMMY(1))))
  707. IF ( LQUERY ) THEN
  708. LWRSVJ = INT(ZWORK(1))
  709. OLWORK = MAX(OLWORK,LWRSVJ)
  710. END IF
  711. END SELECT
  712. IF ( WNTVEC .OR. WNTEX .OR. LSAME(JOBZ,'F') ) THEN
  713. JOBZL = 'V'
  714. ELSE
  715. JOBZL = 'N'
  716. END IF
  717. ! Workspace calculation to the ZGEEV call
  718. MWRKEV = MAX( 1, 2*N )
  719. MLWORK = MAX(MLWORK,MWRKEV)
  720. MLRWRK = MAX(MLRWRK,N+2*N)
  721. IF ( LQUERY ) THEN
  722. CALL ZGEEV( 'N', JOBZL, N, S, LDS, EIGS, &
  723. W, LDW, W, LDW, ZWORK, -1, RWORK, INFO1 )
  724. LWRKEV = INT(ZWORK(1))
  725. OLWORK = MAX( OLWORK, LWRKEV )
  726. END IF
  727. !
  728. IF ( LIWORK < IMINWR .AND. (.NOT.LQUERY) ) INFO = -30
  729. IF ( LRWORK < MLRWRK .AND. (.NOT.LQUERY) ) INFO = -28
  730. IF ( LZWORK < MLWORK .AND. (.NOT.LQUERY) ) INFO = -26
  731. END IF
  732. !
  733. IF( INFO /= 0 ) THEN
  734. CALL XERBLA( 'ZGEDMD', -INFO )
  735. RETURN
  736. ELSE IF ( LQUERY ) THEN
  737. ! Return minimal and optimal workspace sizes
  738. IWORK(1) = IMINWR
  739. RWORK(1) = MLRWRK
  740. ZWORK(1) = MLWORK
  741. ZWORK(2) = OLWORK
  742. RETURN
  743. END IF
  744. !............................................................
  745. !
  746. OFL = DLAMCH('O')
  747. SMALL = DLAMCH('S')
  748. BADXY = .FALSE.
  749. !
  750. ! <1> Optional scaling of the snapshots (columns of X, Y)
  751. ! ==========================================================
  752. IF ( SCCOLX ) THEN
  753. ! The columns of X will be normalized.
  754. ! To prevent overflows, the column norms of X are
  755. ! carefully computed using ZLASSQ.
  756. K = 0
  757. DO i = 1, N
  758. !WORK(i) = DZNRM2( M, X(1,i), 1 )
  759. SSUM = ONE
  760. SCALE = ZERO
  761. CALL ZLASSQ( M, X(1,i), 1, SCALE, SSUM )
  762. IF ( DISNAN(SCALE) .OR. DISNAN(SSUM) ) THEN
  763. K = 0
  764. INFO = -8
  765. CALL XERBLA('ZGEDMD',-INFO)
  766. END IF
  767. IF ( (SCALE /= ZERO) .AND. (SSUM /= ZERO) ) THEN
  768. ROOTSC = SQRT(SSUM)
  769. IF ( SCALE .GE. (OFL / ROOTSC) ) THEN
  770. ! Norm of X(:,i) overflows. First, X(:,i)
  771. ! is scaled by
  772. ! ( ONE / ROOTSC ) / SCALE = 1/||X(:,i)||_2.
  773. ! Next, the norm of X(:,i) is stored without
  774. ! overflow as RWORK(i) = - SCALE * (ROOTSC/M),
  775. ! the minus sign indicating the 1/M factor.
  776. ! Scaling is performed without overflow, and
  777. ! underflow may occur in the smallest entries
  778. ! of X(:,i). The relative backward and forward
  779. ! errors are small in the ell_2 norm.
  780. CALL ZLASCL( 'G', 0, 0, SCALE, ONE/ROOTSC, &
  781. M, 1, X(1,i), LDX, INFO2 )
  782. RWORK(i) = - SCALE * ( ROOTSC / DBLE(M) )
  783. ELSE
  784. ! X(:,i) will be scaled to unit 2-norm
  785. RWORK(i) = SCALE * ROOTSC
  786. CALL ZLASCL( 'G',0, 0, RWORK(i), ONE, M, 1, &
  787. X(1,i), LDX, INFO2 ) ! LAPACK CALL
  788. ! X(1:M,i) = (ONE/RWORK(i)) * X(1:M,i) ! INTRINSIC
  789. END IF
  790. ELSE
  791. RWORK(i) = ZERO
  792. K = K + 1
  793. END IF
  794. END DO
  795. IF ( K == N ) THEN
  796. ! All columns of X are zero. Return error code -8.
  797. ! (the 8th input variable had an illegal value)
  798. K = 0
  799. INFO = -8
  800. CALL XERBLA('ZGEDMD',-INFO)
  801. RETURN
  802. END IF
  803. DO i = 1, N
  804. ! Now, apply the same scaling to the columns of Y.
  805. IF ( RWORK(i) > ZERO ) THEN
  806. CALL ZDSCAL( M, ONE/RWORK(i), Y(1,i), 1 ) ! BLAS CALL
  807. ! Y(1:M,i) = (ONE/RWORK(i)) * Y(1:M,i) ! INTRINSIC
  808. ELSE IF ( RWORK(i) < ZERO ) THEN
  809. CALL ZLASCL( 'G', 0, 0, -RWORK(i), &
  810. ONE/DBLE(M), M, 1, Y(1,i), LDY, INFO2 ) ! LAPACK CALL
  811. ELSE IF ( ABS(Y(IZAMAX(M, Y(1,i),1),i )) &
  812. /= ZERO ) THEN
  813. ! X(:,i) is zero vector. For consistency,
  814. ! Y(:,i) should also be zero. If Y(:,i) is not
  815. ! zero, then the data might be inconsistent or
  816. ! corrupted. If JOBS == 'C', Y(:,i) is set to
  817. ! zero and a warning flag is raised.
  818. ! The computation continues but the
  819. ! situation will be reported in the output.
  820. BADXY = .TRUE.
  821. IF ( LSAME(JOBS,'C')) &
  822. CALL ZDSCAL( M, ZERO, Y(1,i), 1 ) ! BLAS CALL
  823. END IF
  824. END DO
  825. END IF
  826. !
  827. IF ( SCCOLY ) THEN
  828. ! The columns of Y will be normalized.
  829. ! To prevent overflows, the column norms of Y are
  830. ! carefully computed using ZLASSQ.
  831. DO i = 1, N
  832. !RWORK(i) = DZNRM2( M, Y(1,i), 1 )
  833. SSUM = ONE
  834. SCALE = ZERO
  835. CALL ZLASSQ( M, Y(1,i), 1, SCALE, SSUM )
  836. IF ( DISNAN(SCALE) .OR. DISNAN(SSUM) ) THEN
  837. K = 0
  838. INFO = -10
  839. CALL XERBLA('ZGEDMD',-INFO)
  840. END IF
  841. IF ( SCALE /= ZERO .AND. (SSUM /= ZERO) ) THEN
  842. ROOTSC = SQRT(SSUM)
  843. IF ( SCALE .GE. (OFL / ROOTSC) ) THEN
  844. ! Norm of Y(:,i) overflows. First, Y(:,i)
  845. ! is scaled by
  846. ! ( ONE / ROOTSC ) / SCALE = 1/||Y(:,i)||_2.
  847. ! Next, the norm of Y(:,i) is stored without
  848. ! overflow as RWORK(i) = - SCALE * (ROOTSC/M),
  849. ! the minus sign indicating the 1/M factor.
  850. ! Scaling is performed without overflow, and
  851. ! underflow may occur in the smallest entries
  852. ! of Y(:,i). The relative backward and forward
  853. ! errors are small in the ell_2 norm.
  854. CALL ZLASCL( 'G', 0, 0, SCALE, ONE/ROOTSC, &
  855. M, 1, Y(1,i), LDY, INFO2 )
  856. RWORK(i) = - SCALE * ( ROOTSC / DBLE(M) )
  857. ELSE
  858. ! Y(:,i) will be scaled to unit 2-norm
  859. RWORK(i) = SCALE * ROOTSC
  860. CALL ZLASCL( 'G',0, 0, RWORK(i), ONE, M, 1, &
  861. Y(1,i), LDY, INFO2 ) ! LAPACK CALL
  862. ! Y(1:M,i) = (ONE/RWORK(i)) * Y(1:M,i) ! INTRINSIC
  863. END IF
  864. ELSE
  865. RWORK(i) = ZERO
  866. END IF
  867. END DO
  868. DO i = 1, N
  869. ! Now, apply the same scaling to the columns of X.
  870. IF ( RWORK(i) > ZERO ) THEN
  871. CALL ZDSCAL( M, ONE/RWORK(i), X(1,i), 1 ) ! BLAS CALL
  872. ! X(1:M,i) = (ONE/RWORK(i)) * X(1:M,i) ! INTRINSIC
  873. ELSE IF ( RWORK(i) < ZERO ) THEN
  874. CALL ZLASCL( 'G', 0, 0, -RWORK(i), &
  875. ONE/DBLE(M), M, 1, X(1,i), LDX, INFO2 ) ! LAPACK CALL
  876. ELSE IF ( ABS(X(IZAMAX(M, X(1,i),1),i )) &
  877. /= ZERO ) THEN
  878. ! Y(:,i) is zero vector. If X(:,i) is not
  879. ! zero, then a warning flag is raised.
  880. ! The computation continues but the
  881. ! situation will be reported in the output.
  882. BADXY = .TRUE.
  883. END IF
  884. END DO
  885. END IF
  886. !
  887. ! <2> SVD of the data snapshot matrix X.
  888. ! =====================================
  889. ! The left singular vectors are stored in the array X.
  890. ! The right singular vectors are in the array W.
  891. ! The array W will later on contain the eigenvectors
  892. ! of a Rayleigh quotient.
  893. NUMRNK = N
  894. SELECT CASE ( WHTSVD )
  895. CASE (1)
  896. CALL ZGESVD( 'O', 'S', M, N, X, LDX, RWORK, B, &
  897. LDB, W, LDW, ZWORK, LZWORK, RWORK(N+1), INFO1 ) ! LAPACK CALL
  898. T_OR_N = 'C'
  899. CASE (2)
  900. CALL ZGESDD( 'O', M, N, X, LDX, RWORK, B, LDB, W, &
  901. LDW, ZWORK, LZWORK, RWORK(N+1), IWORK, INFO1 ) ! LAPACK CALL
  902. T_OR_N = 'C'
  903. CASE (3)
  904. CALL ZGESVDQ( 'H', 'P', 'N', 'R', 'R', M, N, &
  905. X, LDX, RWORK, Z, LDZ, W, LDW, &
  906. NUMRNK, IWORK, LIWORK, ZWORK, &
  907. LZWORK, RWORK(N+1), LRWORK-N, INFO1) ! LAPACK CALL
  908. CALL ZLACPY( 'A', M, NUMRNK, Z, LDZ, X, LDX ) ! LAPACK CALL
  909. T_OR_N = 'C'
  910. CASE (4)
  911. CALL ZGEJSV( 'F', 'U', JSVOPT, 'R', 'N', 'P', M, &
  912. N, X, LDX, RWORK, Z, LDZ, W, LDW, &
  913. ZWORK, LZWORK, RWORK(N+1), LRWORK-N, IWORK, INFO1 ) ! LAPACK CALL
  914. CALL ZLACPY( 'A', M, N, Z, LDZ, X, LDX ) ! LAPACK CALL
  915. T_OR_N = 'N'
  916. XSCL1 = RWORK(N+1)
  917. XSCL2 = RWORK(N+2)
  918. IF ( XSCL1 /= XSCL2 ) THEN
  919. ! This is an exceptional situation. If the
  920. ! data matrices are not scaled and the
  921. ! largest singular value of X overflows.
  922. ! In that case ZGEJSV can return the SVD
  923. ! in scaled form. The scaling factor can be used
  924. ! to rescale the data (X and Y).
  925. CALL ZLASCL( 'G', 0, 0, XSCL1, XSCL2, M, N, Y, LDY, INFO2 )
  926. END IF
  927. END SELECT
  928. !
  929. IF ( INFO1 > 0 ) THEN
  930. ! The SVD selected subroutine did not converge.
  931. ! Return with an error code.
  932. INFO = 2
  933. RETURN
  934. END IF
  935. !
  936. IF ( RWORK(1) == ZERO ) THEN
  937. ! The largest computed singular value of (scaled)
  938. ! X is zero. Return error code -8
  939. ! (the 8th input variable had an illegal value).
  940. K = 0
  941. INFO = -8
  942. CALL XERBLA('ZGEDMD',-INFO)
  943. RETURN
  944. END IF
  945. !
  946. !<3> Determine the numerical rank of the data
  947. ! snapshots matrix X. This depends on the
  948. ! parameters NRNK and TOL.
  949. SELECT CASE ( NRNK )
  950. CASE ( -1 )
  951. K = 1
  952. DO i = 2, NUMRNK
  953. IF ( ( RWORK(i) <= RWORK(1)*TOL ) .OR. &
  954. ( RWORK(i) <= SMALL ) ) EXIT
  955. K = K + 1
  956. END DO
  957. CASE ( -2 )
  958. K = 1
  959. DO i = 1, NUMRNK-1
  960. IF ( ( RWORK(i+1) <= RWORK(i)*TOL ) .OR. &
  961. ( RWORK(i) <= SMALL ) ) EXIT
  962. K = K + 1
  963. END DO
  964. CASE DEFAULT
  965. K = 1
  966. DO i = 2, NRNK
  967. IF ( RWORK(i) <= SMALL ) EXIT
  968. K = K + 1
  969. END DO
  970. END SELECT
  971. ! Now, U = X(1:M,1:K) is the SVD/POD basis for the
  972. ! snapshot data in the input matrix X.
  973. !<4> Compute the Rayleigh quotient S = U^H * A * U.
  974. ! Depending on the requested outputs, the computation
  975. ! is organized to compute additional auxiliary
  976. ! matrices (for the residuals and refinements).
  977. !
  978. ! In all formulas below, we need V_k*Sigma_k^(-1)
  979. ! where either V_k is in W(1:N,1:K), or V_k^H is in
  980. ! W(1:K,1:N). Here Sigma_k=diag(WORK(1:K)).
  981. IF ( LSAME(T_OR_N, 'N') ) THEN
  982. DO i = 1, K
  983. CALL ZDSCAL( N, ONE/RWORK(i), W(1,i), 1 ) ! BLAS CALL
  984. ! W(1:N,i) = (ONE/RWORK(i)) * W(1:N,i) ! INTRINSIC
  985. END DO
  986. ELSE
  987. ! This non-unit stride access is due to the fact
  988. ! that ZGESVD, ZGESVDQ and ZGESDD return the
  989. ! adjoint matrix of the right singular vectors.
  990. !DO i = 1, K
  991. ! CALL ZDSCAL( N, ONE/RWORK(i), W(i,1), LDW ) ! BLAS CALL
  992. ! ! W(i,1:N) = (ONE/RWORK(i)) * W(i,1:N) ! INTRINSIC
  993. !END DO
  994. DO i = 1, K
  995. RWORK(N+i) = ONE/RWORK(i)
  996. END DO
  997. DO j = 1, N
  998. DO i = 1, K
  999. W(i,j) = CMPLX(RWORK(N+i),ZERO,KIND=WP)*W(i,j)
  1000. END DO
  1001. END DO
  1002. END IF
  1003. !
  1004. IF ( WNTREF ) THEN
  1005. !
  1006. ! Need A*U(:,1:K)=Y*V_k*inv(diag(WORK(1:K)))
  1007. ! for computing the refined Ritz vectors
  1008. ! (optionally, outside ZGEDMD).
  1009. CALL ZGEMM( 'N', T_OR_N, M, K, N, ZONE, Y, LDY, W, &
  1010. LDW, ZZERO, Z, LDZ ) ! BLAS CALL
  1011. ! Z(1:M,1:K)=MATMUL(Y(1:M,1:N),TRANSPOSE(CONJG(W(1:K,1:N)))) ! INTRINSIC, for T_OR_N=='C'
  1012. ! Z(1:M,1:K)=MATMUL(Y(1:M,1:N),W(1:N,1:K)) ! INTRINSIC, for T_OR_N=='N'
  1013. !
  1014. ! At this point Z contains
  1015. ! A * U(:,1:K) = Y * V_k * Sigma_k^(-1), and
  1016. ! this is needed for computing the residuals.
  1017. ! This matrix is returned in the array B and
  1018. ! it can be used to compute refined Ritz vectors.
  1019. CALL ZLACPY( 'A', M, K, Z, LDZ, B, LDB ) ! BLAS CALL
  1020. ! B(1:M,1:K) = Z(1:M,1:K) ! INTRINSIC
  1021. CALL ZGEMM( 'C', 'N', K, K, M, ZONE, X, LDX, Z, &
  1022. LDZ, ZZERO, S, LDS ) ! BLAS CALL
  1023. ! S(1:K,1:K) = MATMUL(TRANSPOSE(CONJG(X(1:M,1:K))),Z(1:M,1:K)) ! INTRINSIC
  1024. ! At this point S = U^H * A * U is the Rayleigh quotient.
  1025. ELSE
  1026. ! A * U(:,1:K) is not explicitly needed and the
  1027. ! computation is organized differently. The Rayleigh
  1028. ! quotient is computed more efficiently.
  1029. CALL ZGEMM( 'C', 'N', K, N, M, ZONE, X, LDX, Y, LDY, &
  1030. ZZERO, Z, LDZ ) ! BLAS CALL
  1031. ! Z(1:K,1:N) = MATMUL( TRANSPOSE(CONJG(X(1:M,1:K))), Y(1:M,1:N) ) ! INTRINSIC
  1032. !
  1033. CALL ZGEMM( 'N', T_OR_N, K, K, N, ZONE, Z, LDZ, W, &
  1034. LDW, ZZERO, S, LDS ) ! BLAS CALL
  1035. ! S(1:K,1:K) = MATMUL(Z(1:K,1:N),TRANSPOSE(CONJG(W(1:K,1:N)))) ! INTRINSIC, for T_OR_N=='T'
  1036. ! S(1:K,1:K) = MATMUL(Z(1:K,1:N),(W(1:N,1:K))) ! INTRINSIC, for T_OR_N=='N'
  1037. ! At this point S = U^H * A * U is the Rayleigh quotient.
  1038. ! If the residuals are requested, save scaled V_k into Z.
  1039. ! Recall that V_k or V_k^H is stored in W.
  1040. IF ( WNTRES .OR. WNTEX ) THEN
  1041. IF ( LSAME(T_OR_N, 'N') ) THEN
  1042. CALL ZLACPY( 'A', N, K, W, LDW, Z, LDZ )
  1043. ELSE
  1044. CALL ZLACPY( 'A', K, N, W, LDW, Z, LDZ )
  1045. END IF
  1046. END IF
  1047. END IF
  1048. !
  1049. !<5> Compute the Ritz values and (if requested) the
  1050. ! right eigenvectors of the Rayleigh quotient.
  1051. !
  1052. CALL ZGEEV( 'N', JOBZL, K, S, LDS, EIGS, W, LDW, &
  1053. W, LDW, ZWORK, LZWORK, RWORK(N+1), INFO1 ) ! LAPACK CALL
  1054. !
  1055. ! W(1:K,1:K) contains the eigenvectors of the Rayleigh
  1056. ! quotient. See the description of Z.
  1057. ! Also, see the description of ZGEEV.
  1058. IF ( INFO1 > 0 ) THEN
  1059. ! ZGEEV failed to compute the eigenvalues and
  1060. ! eigenvectors of the Rayleigh quotient.
  1061. INFO = 3
  1062. RETURN
  1063. END IF
  1064. !
  1065. ! <6> Compute the eigenvectors (if requested) and,
  1066. ! the residuals (if requested).
  1067. !
  1068. IF ( WNTVEC .OR. WNTEX ) THEN
  1069. IF ( WNTRES ) THEN
  1070. IF ( WNTREF ) THEN
  1071. ! Here, if the refinement is requested, we have
  1072. ! A*U(:,1:K) already computed and stored in Z.
  1073. ! For the residuals, need Y = A * U(:,1;K) * W.
  1074. CALL ZGEMM( 'N', 'N', M, K, K, ZONE, Z, LDZ, W, &
  1075. LDW, ZZERO, Y, LDY ) ! BLAS CALL
  1076. ! Y(1:M,1:K) = Z(1:M,1:K) * W(1:K,1:K) ! INTRINSIC
  1077. ! This frees Z; Y contains A * U(:,1:K) * W.
  1078. ELSE
  1079. ! Compute S = V_k * Sigma_k^(-1) * W, where
  1080. ! V_k * Sigma_k^(-1) (or its adjoint) is stored in Z
  1081. CALL ZGEMM( T_OR_N, 'N', N, K, K, ZONE, Z, LDZ, &
  1082. W, LDW, ZZERO, S, LDS )
  1083. ! Then, compute Z = Y * S =
  1084. ! = Y * V_k * Sigma_k^(-1) * W(1:K,1:K) =
  1085. ! = A * U(:,1:K) * W(1:K,1:K)
  1086. CALL ZGEMM( 'N', 'N', M, K, N, ZONE, Y, LDY, S, &
  1087. LDS, ZZERO, Z, LDZ )
  1088. ! Save a copy of Z into Y and free Z for holding
  1089. ! the Ritz vectors.
  1090. CALL ZLACPY( 'A', M, K, Z, LDZ, Y, LDY )
  1091. IF ( WNTEX ) CALL ZLACPY( 'A', M, K, Z, LDZ, B, LDB )
  1092. END IF
  1093. ELSE IF ( WNTEX ) THEN
  1094. ! Compute S = V_k * Sigma_k^(-1) * W, where
  1095. ! V_k * Sigma_k^(-1) is stored in Z
  1096. CALL ZGEMM( T_OR_N, 'N', N, K, K, ZONE, Z, LDZ, &
  1097. W, LDW, ZZERO, S, LDS )
  1098. ! Then, compute Z = Y * S =
  1099. ! = Y * V_k * Sigma_k^(-1) * W(1:K,1:K) =
  1100. ! = A * U(:,1:K) * W(1:K,1:K)
  1101. CALL ZGEMM( 'N', 'N', M, K, N, ZONE, Y, LDY, S, &
  1102. LDS, ZZERO, B, LDB )
  1103. ! The above call replaces the following two calls
  1104. ! that were used in the developing-testing phase.
  1105. ! CALL ZGEMM( 'N', 'N', M, K, N, ZONE, Y, LDY, S, &
  1106. ! LDS, ZZERO, Z, LDZ)
  1107. ! Save a copy of Z into B and free Z for holding
  1108. ! the Ritz vectors.
  1109. ! CALL ZLACPY( 'A', M, K, Z, LDZ, B, LDB )
  1110. END IF
  1111. !
  1112. ! Compute the Ritz vectors
  1113. IF ( WNTVEC ) CALL ZGEMM( 'N', 'N', M, K, K, ZONE, X, LDX, W, LDW, &
  1114. ZZERO, Z, LDZ ) ! BLAS CALL
  1115. ! Z(1:M,1:K) = MATMUL(X(1:M,1:K), W(1:K,1:K)) ! INTRINSIC
  1116. !
  1117. IF ( WNTRES ) THEN
  1118. DO i = 1, K
  1119. CALL ZAXPY( M, -EIGS(i), Z(1,i), 1, Y(1,i), 1 ) ! BLAS CALL
  1120. ! Y(1:M,i) = Y(1:M,i) - EIGS(i) * Z(1:M,i) ! INTRINSIC
  1121. RES(i) = DZNRM2( M, Y(1,i), 1 ) ! BLAS CALL
  1122. END DO
  1123. END IF
  1124. END IF
  1125. !
  1126. IF ( WHTSVD == 4 ) THEN
  1127. RWORK(N+1) = XSCL1
  1128. RWORK(N+2) = XSCL2
  1129. END IF
  1130. !
  1131. ! Successful exit.
  1132. IF ( .NOT. BADXY ) THEN
  1133. INFO = 0
  1134. ELSE
  1135. ! A warning on possible data inconsistency.
  1136. ! This should be a rare event.
  1137. INFO = 4
  1138. END IF
  1139. !............................................................
  1140. RETURN
  1141. ! ......
  1142. END SUBROUTINE ZGEDMD