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.

cgedmd.f90 48 kB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151
  1. !> \brief \b CGEDMD computes the Dynamic Mode Decomposition (DMD) for a pair of data snapshot matrices.
  2. !
  3. ! =========== DOCUMENTATION ===========
  4. !
  5. ! Definition:
  6. ! ===========
  7. !
  8. ! SUBROUTINE CGEDMD( 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 = real32
  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. !> CGEDMD 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, CGEDMD 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, CGEDMD 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 :: CGESVD (the QR SVD algorithm)
  171. !> 2 :: CGESDD (the Divide and Conquer algorithm; if enough
  172. !> workspace available, this is the fastest option)
  173. !> 3 :: CGESVDQ (the preconditioned QR SVD ; this and 4
  174. !> are the most accurate options)
  175. !> 4 :: CGEJSV (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,out] X
  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. !> \endverbatim
  214. !.....
  215. !> \param[in] LDX
  216. !> \verbatim
  217. !> LDX (input) INTEGER, LDX >= M
  218. !> The leading dimension of the array X.
  219. !> \endverbatim
  220. !.....
  221. !> \param[in,out] Y
  222. !> \verbatim
  223. !> Y (input/workspace/output) COMPLEX(KIND=WP) M-by-N array
  224. !> > On entry, Y contains the data snapshot matrix Y
  225. !> < On exit,
  226. !> If JOBR == 'R', the leading K columns of Y contain
  227. !> the residual vectors for the computed Ritz pairs.
  228. !> See the description of RES.
  229. !> If JOBR == 'N', Y contains the original input data,
  230. !> scaled according to the value of JOBS.
  231. !> \endverbatim
  232. !.....
  233. !> \param[in] LDY
  234. !> \verbatim
  235. !> LDY (input) INTEGER , LDY >= M
  236. !> The leading dimension of the array Y.
  237. !> \endverbatim
  238. !.....
  239. !> \param[in] NRNK
  240. !> \verbatim
  241. !> NRNK (input) INTEGER
  242. !> Determines the mode how to compute the numerical rank,
  243. !> i.e. how to truncate small singular values of the input
  244. !> matrix X. On input, if
  245. !> NRNK = -1 :: i-th singular value sigma(i) is truncated
  246. !> if sigma(i) <= TOL*sigma(1)
  247. !> This option is recommended.
  248. !> NRNK = -2 :: i-th singular value sigma(i) is truncated
  249. !> if sigma(i) <= TOL*sigma(i-1)
  250. !> This option is included for R&D purposes.
  251. !> It requires highly accurate SVD, which
  252. !> may not be feasible.
  253. !> The numerical rank can be enforced by using positive
  254. !> value of NRNK as follows:
  255. !> 0 < NRNK <= N :: at most NRNK largest singular values
  256. !> will be used. If the number of the computed nonzero
  257. !> singular values is less than NRNK, then only those
  258. !> nonzero values will be used and the actually used
  259. !> dimension is less than NRNK. The actual number of
  260. !> the nonzero singular values is returned in the variable
  261. !> K. See the descriptions of TOL and K.
  262. !> \endverbatim
  263. !.....
  264. !> \param[in] TOL
  265. !> \verbatim
  266. !> TOL (input) REAL(KIND=WP), 0 <= TOL < 1
  267. !> The tolerance for truncating small singular values.
  268. !> See the description of NRNK.
  269. !> \endverbatim
  270. !.....
  271. !> \param[out] K
  272. !> \verbatim
  273. !> K (output) INTEGER, 0 <= K <= N
  274. !> The dimension of the POD basis for the data snapshot
  275. !> matrix X and the number of the computed Ritz pairs.
  276. !> The value of K is determined according to the rule set
  277. !> by the parameters NRNK and TOL.
  278. !> See the descriptions of NRNK and TOL.
  279. !> \endverbatim
  280. !.....
  281. !> \param[out] EIGS
  282. !> \verbatim
  283. !> EIGS (output) COMPLEX(KIND=WP) N-by-1 array
  284. !> The leading K (K<=N) entries of EIGS contain
  285. !> the computed eigenvalues (Ritz values).
  286. !> See the descriptions of K, and Z.
  287. !> \endverbatim
  288. !.....
  289. !> \param[out] Z
  290. !> \verbatim
  291. !> Z (workspace/output) COMPLEX(KIND=WP) M-by-N array
  292. !> If JOBZ =='V' then Z contains the Ritz vectors. Z(:,i)
  293. !> is an eigenvector of the i-th Ritz value; ||Z(:,i)||_2=1.
  294. !> If JOBZ == 'F', then the Z(:,i)'s are given implicitly as
  295. !> the columns of X(:,1:K)*W(1:K,1:K), i.e. X(:,1:K)*W(:,i)
  296. !> is an eigenvector corresponding to EIGS(i). The columns
  297. !> of W(1:k,1:K) are the computed eigenvectors of the
  298. !> K-by-K Rayleigh quotient.
  299. !> See the descriptions of EIGS, X and W.
  300. !> \endverbatim
  301. !.....
  302. !> \param[in] LDZ
  303. !> \verbatim
  304. !> LDZ (input) INTEGER , LDZ >= M
  305. !> The leading dimension of the array Z.
  306. !> \endverbatim
  307. !.....
  308. !> \param[out] RES
  309. !> \verbatim
  310. !> RES (output) REAL(KIND=WP) N-by-1 array
  311. !> RES(1:K) contains the residuals for the K computed
  312. !> Ritz pairs,
  313. !> RES(i) = || A * Z(:,i) - EIGS(i)*Z(:,i))||_2.
  314. !> See the description of EIGS and Z.
  315. !> \endverbatim
  316. !.....
  317. !> \param[out] B
  318. !> \verbatim
  319. !> B (output) COMPLEX(KIND=WP) M-by-N array.
  320. !> IF JOBF =='R', B(1:M,1:K) contains A*U(:,1:K), and can
  321. !> be used for computing the refined vectors; see further
  322. !> details in the provided references.
  323. !> If JOBF == 'E', B(1:M,1:K) contains
  324. !> A*U(:,1:K)*W(1:K,1:K), which are the vectors from the
  325. !> Exact DMD, up to scaling by the inverse eigenvalues.
  326. !> If JOBF =='N', then B is not referenced.
  327. !> See the descriptions of X, W, K.
  328. !> \endverbatim
  329. !.....
  330. !> \param[in] LDB
  331. !> \verbatim
  332. !> LDB (input) INTEGER, LDB >= M
  333. !> The leading dimension of the array B.
  334. !> \endverbatim
  335. !.....
  336. !> \param[out] W
  337. !> \verbatim
  338. !> W (workspace/output) COMPLEX(KIND=WP) N-by-N array
  339. !> On exit, W(1:K,1:K) contains the K computed
  340. !> eigenvectors of the matrix Rayleigh quotient.
  341. !> The Ritz vectors (returned in Z) are the
  342. !> product of X (containing a POD basis for the input
  343. !> matrix X) and W. See the descriptions of K, S, X and Z.
  344. !> W is also used as a workspace to temporarily store the
  345. !> right singular vectors of X.
  346. !> \endverbatim
  347. !.....
  348. !> \param[in] LDW
  349. !> \verbatim
  350. !> LDW (input) INTEGER, LDW >= N
  351. !> The leading dimension of the array W.
  352. !> \endverbatim
  353. !.....
  354. !> \param[out] S
  355. !> \verbatim
  356. !> S (workspace/output) COMPLEX(KIND=WP) N-by-N array
  357. !> The array S(1:K,1:K) is used for the matrix Rayleigh
  358. !> quotient. This content is overwritten during
  359. !> the eigenvalue decomposition by CGEEV.
  360. !> See the description of K.
  361. !> \endverbatim
  362. !.....
  363. !> \param[in] LDS
  364. !> \verbatim
  365. !> LDS (input) INTEGER, LDS >= N
  366. !> The leading dimension of the array S.
  367. !> \endverbatim
  368. !.....
  369. !> \param[out] ZWORK
  370. !> \verbatim
  371. !> ZWORK (workspace/output) COMPLEX(KIND=WP) LZWORK-by-1 array
  372. !> ZWORK is used as complex workspace in the complex SVD, as
  373. !> specified by WHTSVD (1,2, 3 or 4) and for CGEEV for computing
  374. !> the eigenvalues of a Rayleigh quotient.
  375. !> If the call to CGEDMD is only workspace query, then
  376. !> ZWORK(1) contains the minimal complex workspace length and
  377. !> ZWORK(2) is the optimal complex workspace length.
  378. !> Hence, the length of work is at least 2.
  379. !> See the description of LZWORK.
  380. !> \endverbatim
  381. !.....
  382. !> \param[in] LZWORK
  383. !> \verbatim
  384. !> LZWORK (input) INTEGER
  385. !> The minimal length of the workspace vector ZWORK.
  386. !> LZWORK is calculated as MAX(LZWORK_SVD, LZWORK_CGEEV),
  387. !> where LZWORK_CGEEV = MAX( 1, 2*N ) and the minimal
  388. !> LZWORK_SVD is calculated as follows
  389. !> If WHTSVD == 1 :: CGESVD ::
  390. !> LZWORK_SVD = MAX(1,2*MIN(M,N)+MAX(M,N))
  391. !> If WHTSVD == 2 :: CGESDD ::
  392. !> LZWORK_SVD = 2*MIN(M,N)*MIN(M,N)+2*MIN(M,N)+MAX(M,N)
  393. !> If WHTSVD == 3 :: CGESVDQ ::
  394. !> LZWORK_SVD = obtainable by a query
  395. !> If WHTSVD == 4 :: CGEJSV ::
  396. !> LZWORK_SVD = obtainable by a query
  397. !> If on entry LZWORK = -1, then a workspace query is
  398. !> assumed and the procedure only computes the minimal
  399. !> and the optimal workspace lengths and returns them in
  400. !> LZWORK(1) and LZWORK(2), respectively.
  401. !> \endverbatim
  402. !.....
  403. !> \param[out] RWORK
  404. !> \verbatim
  405. !> RWORK (workspace/output) REAL(KIND=WP) LRWORK-by-1 array
  406. !> On exit, RWORK(1:N) contains the singular values of
  407. !> X (for JOBS=='N') or column scaled X (JOBS=='S', 'C').
  408. !> If WHTSVD==4, then RWORK(N+1) and RWORK(N+2) contain
  409. !> scaling factor RWORK(N+2)/RWORK(N+1) used to scale X
  410. !> and Y to avoid overflow in the SVD of X.
  411. !> This may be of interest if the scaling option is off
  412. !> and as many as possible smallest eigenvalues are
  413. !> desired to the highest feasible accuracy.
  414. !> If the call to CGEDMD is only workspace query, then
  415. !> RWORK(1) contains the minimal workspace length.
  416. !> See the description of LRWORK.
  417. !> \endverbatim
  418. !.....
  419. !> \param[in] LRWORK
  420. !> \verbatim
  421. !> LRWORK (input) INTEGER
  422. !> The minimal length of the workspace vector RWORK.
  423. !> LRWORK is calculated as follows:
  424. !> LRWORK = MAX(1, N+LRWORK_SVD,N+LRWORK_CGEEV), where
  425. !> LRWORK_CGEEV = MAX(1,2*N) and RWORK_SVD is the real workspace
  426. !> for the SVD subroutine determined by the input parameter
  427. !> WHTSVD.
  428. !> If WHTSVD == 1 :: CGESVD ::
  429. !> LRWORK_SVD = 5*MIN(M,N)
  430. !> If WHTSVD == 2 :: CGESDD ::
  431. !> LRWORK_SVD = MAX(5*MIN(M,N)*MIN(M,N)+7*MIN(M,N),
  432. !> 2*MAX(M,N)*MIN(M,N)+2*MIN(M,N)*MIN(M,N)+MIN(M,N) ) )
  433. !> If WHTSVD == 3 :: CGESVDQ ::
  434. !> LRWORK_SVD = obtainable by a query
  435. !> If WHTSVD == 4 :: CGEJSV ::
  436. !> LRWORK_SVD = obtainable by a query
  437. !> If on entry LRWORK = -1, then a workspace query is
  438. !> assumed and the procedure only computes the minimal
  439. !> real workspace length and returns it in RWORK(1).
  440. !> \endverbatim
  441. !.....
  442. !> \param[out] IWORK
  443. !> \verbatim
  444. !> IWORK (workspace/output) INTEGER LIWORK-by-1 array
  445. !> Workspace that is required only if WHTSVD equals
  446. !> 2 , 3 or 4. (See the description of WHTSVD).
  447. !> If on entry LWORK =-1 or LIWORK=-1, then the
  448. !> minimal length of IWORK is computed and returned in
  449. !> IWORK(1). See the description of LIWORK.
  450. !> \endverbatim
  451. !.....
  452. !> \param[in] LIWORK
  453. !> \verbatim
  454. !> LIWORK (input) INTEGER
  455. !> The minimal length of the workspace vector IWORK.
  456. !> If WHTSVD == 1, then only IWORK(1) is used; LIWORK >=1
  457. !> If WHTSVD == 2, then LIWORK >= MAX(1,8*MIN(M,N))
  458. !> If WHTSVD == 3, then LIWORK >= MAX(1,M+N-1)
  459. !> If WHTSVD == 4, then LIWORK >= MAX(3,M+3*N)
  460. !> If on entry LIWORK = -1, then a workspace query is
  461. !> assumed and the procedure only computes the minimal
  462. !> and the optimal workspace lengths for ZWORK, RWORK and
  463. !> IWORK. See the descriptions of ZWORK, RWORK and IWORK.
  464. !> \endverbatim
  465. !.....
  466. !> \param[out] INFO
  467. !> \verbatim
  468. !> INFO (output) INTEGER
  469. !> -i < 0 :: On entry, the i-th argument had an
  470. !> illegal value
  471. !> = 0 :: Successful return.
  472. !> = 1 :: Void input. Quick exit (M=0 or N=0).
  473. !> = 2 :: The SVD computation of X did not converge.
  474. !> Suggestion: Check the input data and/or
  475. !> repeat with different WHTSVD.
  476. !> = 3 :: The computation of the eigenvalues did not
  477. !> converge.
  478. !> = 4 :: If data scaling was requested on input and
  479. !> the procedure found inconsistency in the data
  480. !> such that for some column index i,
  481. !> X(:,i) = 0 but Y(:,i) /= 0, then Y(:,i) is set
  482. !> to zero if JOBS=='C'. The computation proceeds
  483. !> with original or modified data and warning
  484. !> flag is set with INFO=4.
  485. !> \endverbatim
  486. !
  487. ! Authors:
  488. ! ========
  489. !
  490. !> \author Zlatko Drmac
  491. !
  492. !> \ingroup gedmd
  493. !
  494. !.............................................................
  495. !.............................................................
  496. SUBROUTINE CGEDMD( JOBS, JOBZ, JOBR, JOBF, WHTSVD, &
  497. M, N, X, LDX, Y, LDY, NRNK, TOL, &
  498. K, EIGS, Z, LDZ, RES, B, LDB, &
  499. W, LDW, S, LDS, ZWORK, LZWORK, &
  500. RWORK, LRWORK, IWORK, LIWORK, INFO )
  501. !
  502. ! -- LAPACK driver routine --
  503. !
  504. ! -- LAPACK is a software package provided by University of --
  505. ! -- Tennessee, University of California Berkeley, University of --
  506. ! -- Colorado Denver and NAG Ltd.. --
  507. !
  508. !.....
  509. USE iso_fortran_env
  510. IMPLICIT NONE
  511. INTEGER, PARAMETER :: WP = real32
  512. !
  513. ! Scalar arguments
  514. ! ~~~~~~~~~~~~~~~~
  515. CHARACTER, INTENT(IN) :: JOBS, JOBZ, JOBR, JOBF
  516. INTEGER, INTENT(IN) :: WHTSVD, M, N, LDX, LDY, &
  517. NRNK, LDZ, LDB, LDW, LDS, &
  518. LIWORK, LRWORK, LZWORK
  519. INTEGER, INTENT(OUT) :: K, INFO
  520. REAL(KIND=WP), INTENT(IN) :: TOL
  521. !
  522. ! Array arguments
  523. ! ~~~~~~~~~~~~~~~
  524. COMPLEX(KIND=WP), INTENT(INOUT) :: X(LDX,*), Y(LDY,*)
  525. COMPLEX(KIND=WP), INTENT(OUT) :: Z(LDZ,*), B(LDB,*), &
  526. W(LDW,*), S(LDS,*)
  527. COMPLEX(KIND=WP), INTENT(OUT) :: EIGS(*)
  528. COMPLEX(KIND=WP), INTENT(OUT) :: ZWORK(*)
  529. REAL(KIND=WP), INTENT(OUT) :: RES(*)
  530. REAL(KIND=WP), INTENT(OUT) :: RWORK(*)
  531. INTEGER, INTENT(OUT) :: IWORK(*)
  532. !
  533. ! Parameters
  534. ! ~~~~~~~~~~
  535. REAL(KIND=WP), PARAMETER :: ONE = 1.0_WP
  536. REAL(KIND=WP), PARAMETER :: ZERO = 0.0_WP
  537. COMPLEX(KIND=WP), PARAMETER :: ZONE = ( 1.0_WP, 0.0_WP )
  538. COMPLEX(KIND=WP), PARAMETER :: ZZERO = ( 0.0_WP, 0.0_WP )
  539. !
  540. ! Local scalars
  541. ! ~~~~~~~~~~~~~
  542. REAL(KIND=WP) :: OFL, ROOTSC, SCALE, SMALL, &
  543. SSUM, XSCL1, XSCL2
  544. INTEGER :: i, j, IMINWR, INFO1, INFO2, &
  545. LWRKEV, LWRSDD, LWRSVD, LWRSVJ, &
  546. LWRSVQ, MLWORK, MWRKEV, MWRSDD, &
  547. MWRSVD, MWRSVJ, MWRSVQ, NUMRNK, &
  548. OLWORK, MLRWRK
  549. LOGICAL :: BADXY, LQUERY, SCCOLX, SCCOLY, &
  550. WNTEX, WNTREF, WNTRES, WNTVEC
  551. CHARACTER :: JOBZL, T_OR_N
  552. CHARACTER :: JSVOPT
  553. !
  554. ! Local arrays
  555. ! ~~~~~~~~~~~~
  556. REAL(KIND=WP) :: RDUMMY(2)
  557. !
  558. ! External functions (BLAS and LAPACK)
  559. ! ~~~~~~~~~~~~~~~~~
  560. REAL(KIND=WP) CLANGE, SLAMCH, SCNRM2
  561. EXTERNAL CLANGE, SLAMCH, SCNRM2, ICAMAX
  562. INTEGER ICAMAX
  563. LOGICAL SISNAN, LSAME
  564. EXTERNAL SISNAN, LSAME
  565. !
  566. ! External subroutines (BLAS and LAPACK)
  567. ! ~~~~~~~~~~~~~~~~~~~~
  568. EXTERNAL CAXPY, CGEMM, CSSCAL
  569. EXTERNAL CGEEV, CGEJSV, CGESDD, CGESVD, CGESVDQ, &
  570. CLACPY, CLASCL, CLASSQ, XERBLA
  571. !
  572. ! Intrinsic functions
  573. ! ~~~~~~~~~~~~~~~~~~~
  574. INTRINSIC FLOAT, INT, MAX, SQRT
  575. !............................................................
  576. !
  577. ! Test the input arguments
  578. !
  579. WNTRES = LSAME(JOBR,'R')
  580. SCCOLX = LSAME(JOBS,'S') .OR. LSAME(JOBS,'C')
  581. SCCOLY = LSAME(JOBS,'Y')
  582. WNTVEC = LSAME(JOBZ,'V')
  583. WNTREF = LSAME(JOBF,'R')
  584. WNTEX = LSAME(JOBF,'E')
  585. INFO = 0
  586. LQUERY = ( ( LZWORK == -1 ) .OR. ( LIWORK == -1 ) &
  587. .OR. ( LRWORK == -1 ) )
  588. !
  589. IF ( .NOT. (SCCOLX .OR. SCCOLY .OR. &
  590. LSAME(JOBS,'N')) ) THEN
  591. INFO = -1
  592. ELSE IF ( .NOT. (WNTVEC .OR. LSAME(JOBZ,'N') &
  593. .OR. LSAME(JOBZ,'F')) ) THEN
  594. INFO = -2
  595. ELSE IF ( .NOT. (WNTRES .OR. LSAME(JOBR,'N')) .OR. &
  596. ( WNTRES .AND. (.NOT.WNTVEC) ) ) THEN
  597. INFO = -3
  598. ELSE IF ( .NOT. (WNTREF .OR. WNTEX .OR. &
  599. LSAME(JOBF,'N') ) ) THEN
  600. INFO = -4
  601. ELSE IF ( .NOT.((WHTSVD == 1) .OR. (WHTSVD == 2) .OR. &
  602. (WHTSVD == 3) .OR. (WHTSVD == 4) )) THEN
  603. INFO = -5
  604. ELSE IF ( M < 0 ) THEN
  605. INFO = -6
  606. ELSE IF ( ( N < 0 ) .OR. ( N > M ) ) THEN
  607. INFO = -7
  608. ELSE IF ( LDX < M ) THEN
  609. INFO = -9
  610. ELSE IF ( LDY < M ) THEN
  611. INFO = -11
  612. ELSE IF ( .NOT. (( NRNK == -2).OR.(NRNK == -1).OR. &
  613. ((NRNK >= 1).AND.(NRNK <=N ))) ) THEN
  614. INFO = -12
  615. ELSE IF ( ( TOL < ZERO ) .OR. ( TOL >= ONE ) ) THEN
  616. INFO = -13
  617. ELSE IF ( LDZ < M ) THEN
  618. INFO = -17
  619. ELSE IF ( (WNTREF .OR. WNTEX ) .AND. ( LDB < M ) ) THEN
  620. INFO = -20
  621. ELSE IF ( LDW < N ) THEN
  622. INFO = -22
  623. ELSE IF ( LDS < N ) THEN
  624. INFO = -24
  625. END IF
  626. !
  627. IF ( INFO == 0 ) THEN
  628. ! Compute the minimal and the optimal workspace
  629. ! requirements. Simulate running the code and
  630. ! determine minimal and optimal sizes of the
  631. ! workspace at any moment of the run.
  632. IF ( N == 0 ) THEN
  633. ! Quick return. All output except K is void.
  634. ! INFO=1 signals the void input.
  635. ! In case of a workspace query, the default
  636. ! minimal workspace lengths are returned.
  637. IF ( LQUERY ) THEN
  638. IWORK(1) = 1
  639. RWORK(1) = 1
  640. ZWORK(1) = 2
  641. ZWORK(2) = 2
  642. ELSE
  643. K = 0
  644. END IF
  645. INFO = 1
  646. RETURN
  647. END IF
  648. IMINWR = 1
  649. MLRWRK = MAX(1,N)
  650. MLWORK = 2
  651. OLWORK = 2
  652. SELECT CASE ( WHTSVD )
  653. CASE (1)
  654. ! The following is specified as the minimal
  655. ! length of WORK in the definition of CGESVD:
  656. ! MWRSVD = MAX(1,2*MIN(M,N)+MAX(M,N))
  657. MWRSVD = MAX(1,2*MIN(M,N)+MAX(M,N))
  658. MLWORK = MAX(MLWORK,MWRSVD)
  659. MLRWRK = MAX(MLRWRK,N + 5*MIN(M,N))
  660. IF ( LQUERY ) THEN
  661. CALL CGESVD( 'O', 'S', M, N, X, LDX, RWORK, &
  662. B, LDB, W, LDW, ZWORK, -1, RDUMMY, INFO1 )
  663. LWRSVD = INT( ZWORK(1) )
  664. OLWORK = MAX(OLWORK,LWRSVD)
  665. END IF
  666. CASE (2)
  667. ! The following is specified as the minimal
  668. ! length of WORK in the definition of CGESDD:
  669. ! MWRSDD = 2*min(M,N)*min(M,N)+2*min(M,N)+max(M,N).
  670. ! RWORK length: 5*MIN(M,N)*MIN(M,N)+7*MIN(M,N)
  671. ! In LAPACK 3.10.1 RWORK is defined differently.
  672. ! Below we take max over the two versions.
  673. ! IMINWR = 8*MIN(M,N)
  674. MWRSDD = 2*MIN(M,N)*MIN(M,N)+2*MIN(M,N)+MAX(M,N)
  675. MLWORK = MAX(MLWORK,MWRSDD)
  676. IMINWR = 8*MIN(M,N)
  677. MLRWRK = MAX( MLRWRK, N + &
  678. MAX( 5*MIN(M,N)*MIN(M,N)+7*MIN(M,N), &
  679. 5*MIN(M,N)*MIN(M,N)+5*MIN(M,N), &
  680. 2*MAX(M,N)*MIN(M,N)+ &
  681. 2*MIN(M,N)*MIN(M,N)+MIN(M,N) ) )
  682. IF ( LQUERY ) THEN
  683. CALL CGESDD( 'O', M, N, X, LDX, RWORK, B, &
  684. LDB, W, LDW, ZWORK, -1, RDUMMY, IWORK, INFO1 )
  685. LWRSDD = MAX(MWRSDD,INT( ZWORK(1) ))
  686. OLWORK = MAX(OLWORK,LWRSDD)
  687. END IF
  688. CASE (3)
  689. CALL CGESVDQ( 'H', 'P', 'N', 'R', 'R', M, N, &
  690. X, LDX, RWORK, Z, LDZ, W, LDW, NUMRNK, &
  691. IWORK, -1, ZWORK, -1, RDUMMY, -1, INFO1 )
  692. IMINWR = IWORK(1)
  693. MWRSVQ = INT(ZWORK(2))
  694. MLWORK = MAX(MLWORK,MWRSVQ)
  695. MLRWRK = MAX(MLRWRK,N + INT(RDUMMY(1)))
  696. IF ( LQUERY ) THEN
  697. LWRSVQ = INT(ZWORK(1))
  698. OLWORK = MAX(OLWORK,LWRSVQ)
  699. END IF
  700. CASE (4)
  701. JSVOPT = 'J'
  702. CALL CGEJSV( 'F', 'U', JSVOPT, 'N', 'N', 'P', M, &
  703. N, X, LDX, RWORK, Z, LDZ, W, LDW, &
  704. ZWORK, -1, RDUMMY, -1, IWORK, INFO1 )
  705. IMINWR = IWORK(1)
  706. MWRSVJ = INT(ZWORK(2))
  707. MLWORK = MAX(MLWORK,MWRSVJ)
  708. MLRWRK = MAX(MLRWRK,N + MAX(7,INT(RDUMMY(1))))
  709. IF ( LQUERY ) THEN
  710. LWRSVJ = INT(ZWORK(1))
  711. OLWORK = MAX(OLWORK,LWRSVJ)
  712. END IF
  713. END SELECT
  714. IF ( WNTVEC .OR. WNTEX .OR. LSAME(JOBZ,'F') ) THEN
  715. JOBZL = 'V'
  716. ELSE
  717. JOBZL = 'N'
  718. END IF
  719. ! Workspace calculation to the CGEEV call
  720. MWRKEV = MAX( 1, 2*N )
  721. MLWORK = MAX(MLWORK,MWRKEV)
  722. MLRWRK = MAX(MLRWRK,N+2*N)
  723. IF ( LQUERY ) THEN
  724. CALL CGEEV( 'N', JOBZL, N, S, LDS, EIGS, &
  725. W, LDW, W, LDW, ZWORK, -1, RWORK, INFO1 ) ! LAPACK CALL
  726. LWRKEV = INT(ZWORK(1))
  727. OLWORK = MAX( OLWORK, LWRKEV )
  728. OLWORK = MAX( 2, OLWORK )
  729. END IF
  730. !
  731. IF ( LIWORK < IMINWR .AND. (.NOT.LQUERY) ) INFO = -30
  732. IF ( LRWORK < MLRWRK .AND. (.NOT.LQUERY) ) INFO = -28
  733. IF ( LZWORK < MLWORK .AND. (.NOT.LQUERY) ) INFO = -26
  734. END IF
  735. !
  736. IF( INFO /= 0 ) THEN
  737. CALL XERBLA( 'CGEDMD', -INFO )
  738. RETURN
  739. ELSE IF ( LQUERY ) THEN
  740. ! Return minimal and optimal workspace sizes
  741. IWORK(1) = IMINWR
  742. RWORK(1) = MLRWRK
  743. ZWORK(1) = MLWORK
  744. ZWORK(2) = OLWORK
  745. RETURN
  746. END IF
  747. !............................................................
  748. !
  749. OFL = SLAMCH('O')*SLAMCH('P')
  750. SMALL = SLAMCH('S')
  751. BADXY = .FALSE.
  752. !
  753. ! <1> Optional scaling of the snapshots (columns of X, Y)
  754. ! ==========================================================
  755. IF ( SCCOLX ) THEN
  756. ! The columns of X will be normalized.
  757. ! To prevent overflows, the column norms of X are
  758. ! carefully computed using CLASSQ.
  759. K = 0
  760. DO i = 1, N
  761. !WORK(i) = SCNRM2( M, X(1,i), 1 )
  762. SSUM = ONE
  763. SCALE = ZERO
  764. CALL CLASSQ( M, X(1,i), 1, SCALE, SSUM )
  765. IF ( SISNAN(SCALE) .OR. SISNAN(SSUM) ) THEN
  766. K = 0
  767. INFO = -8
  768. CALL XERBLA('CGEDMD',-INFO)
  769. END IF
  770. IF ( (SCALE /= ZERO) .AND. (SSUM /= ZERO) ) THEN
  771. ROOTSC = SQRT(SSUM)
  772. IF ( SCALE .GE. (OFL / ROOTSC) ) THEN
  773. ! Norm of X(:,i) overflows. First, X(:,i)
  774. ! is scaled by
  775. ! ( ONE / ROOTSC ) / SCALE = 1/||X(:,i)||_2.
  776. ! Next, the norm of X(:,i) is stored without
  777. ! overflow as WORK(i) = - SCALE * (ROOTSC/M),
  778. ! the minus sign indicating the 1/M factor.
  779. ! Scaling is performed without overflow, and
  780. ! underflow may occur in the smallest entries
  781. ! of X(:,i). The relative backward and forward
  782. ! errors are small in the ell_2 norm.
  783. CALL CLASCL( 'G', 0, 0, SCALE, ONE/ROOTSC, &
  784. M, 1, X(1,i), LDX, INFO2 )
  785. RWORK(i) = - SCALE * ( ROOTSC / FLOAT(M) )
  786. ELSE
  787. ! X(:,i) will be scaled to unit 2-norm
  788. RWORK(i) = SCALE * ROOTSC
  789. CALL CLASCL( 'G',0, 0, RWORK(i), ONE, M, 1, &
  790. X(1,i), LDX, INFO2 ) ! LAPACK CALL
  791. ! X(1:M,i) = (ONE/RWORK(i)) * X(1:M,i) ! INTRINSIC
  792. END IF
  793. ELSE
  794. RWORK(i) = ZERO
  795. K = K + 1
  796. END IF
  797. END DO
  798. IF ( K == N ) THEN
  799. ! All columns of X are zero. Return error code -8.
  800. ! (the 8th input variable had an illegal value)
  801. K = 0
  802. INFO = -8
  803. CALL XERBLA('CGEDMD',-INFO)
  804. RETURN
  805. END IF
  806. DO i = 1, N
  807. ! Now, apply the same scaling to the columns of Y.
  808. IF ( RWORK(i) > ZERO ) THEN
  809. CALL CSSCAL( M, ONE/RWORK(i), Y(1,i), 1 ) ! BLAS CALL
  810. ! Y(1:M,i) = (ONE/RWORK(i)) * Y(1:M,i) ! INTRINSIC
  811. ELSE IF ( RWORK(i) < ZERO ) THEN
  812. CALL CLASCL( 'G', 0, 0, -RWORK(i), &
  813. ONE/FLOAT(M), M, 1, Y(1,i), LDY, INFO2 ) ! LAPACK CALL
  814. ELSE IF ( ABS(Y(ICAMAX(M, Y(1,i),1),i )) &
  815. /= ZERO ) THEN
  816. ! X(:,i) is zero vector. For consistency,
  817. ! Y(:,i) should also be zero. If Y(:,i) is not
  818. ! zero, then the data might be inconsistent or
  819. ! corrupted. If JOBS == 'C', Y(:,i) is set to
  820. ! zero and a warning flag is raised.
  821. ! The computation continues but the
  822. ! situation will be reported in the output.
  823. BADXY = .TRUE.
  824. IF ( LSAME(JOBS,'C')) &
  825. CALL CSSCAL( M, ZERO, Y(1,i), 1 ) ! BLAS CALL
  826. END IF
  827. END DO
  828. END IF
  829. !
  830. IF ( SCCOLY ) THEN
  831. ! The columns of Y will be normalized.
  832. ! To prevent overflows, the column norms of Y are
  833. ! carefully computed using CLASSQ.
  834. DO i = 1, N
  835. !RWORK(i) = SCNRM2( M, Y(1,i), 1 )
  836. SSUM = ONE
  837. SCALE = ZERO
  838. CALL CLASSQ( M, Y(1,i), 1, SCALE, SSUM )
  839. IF ( SISNAN(SCALE) .OR. SISNAN(SSUM) ) THEN
  840. K = 0
  841. INFO = -10
  842. CALL XERBLA('CGEDMD',-INFO)
  843. END IF
  844. IF ( SCALE /= ZERO .AND. (SSUM /= ZERO) ) THEN
  845. ROOTSC = SQRT(SSUM)
  846. IF ( SCALE .GE. (OFL / ROOTSC) ) THEN
  847. ! Norm of Y(:,i) overflows. First, Y(:,i)
  848. ! is scaled by
  849. ! ( ONE / ROOTSC ) / SCALE = 1/||Y(:,i)||_2.
  850. ! Next, the norm of Y(:,i) is stored without
  851. ! overflow as RWORK(i) = - SCALE * (ROOTSC/M),
  852. ! the minus sign indicating the 1/M factor.
  853. ! Scaling is performed without overflow, and
  854. ! underflow may occur in the smallest entries
  855. ! of Y(:,i). The relative backward and forward
  856. ! errors are small in the ell_2 norm.
  857. CALL CLASCL( 'G', 0, 0, SCALE, ONE/ROOTSC, &
  858. M, 1, Y(1,i), LDY, INFO2 )
  859. RWORK(i) = - SCALE * ( ROOTSC / FLOAT(M) )
  860. ELSE
  861. ! Y(:,i) will be scaled to unit 2-norm
  862. RWORK(i) = SCALE * ROOTSC
  863. CALL CLASCL( 'G',0, 0, RWORK(i), ONE, M, 1, &
  864. Y(1,i), LDY, INFO2 ) ! LAPACK CALL
  865. ! Y(1:M,i) = (ONE/RWORK(i)) * Y(1:M,i) ! INTRINSIC
  866. END IF
  867. ELSE
  868. RWORK(i) = ZERO
  869. END IF
  870. END DO
  871. DO i = 1, N
  872. ! Now, apply the same scaling to the columns of X.
  873. IF ( RWORK(i) > ZERO ) THEN
  874. CALL CSSCAL( M, ONE/RWORK(i), X(1,i), 1 ) ! BLAS CALL
  875. ! X(1:M,i) = (ONE/RWORK(i)) * X(1:M,i) ! INTRINSIC
  876. ELSE IF ( RWORK(i) < ZERO ) THEN
  877. CALL CLASCL( 'G', 0, 0, -RWORK(i), &
  878. ONE/FLOAT(M), M, 1, X(1,i), LDX, INFO2 ) ! LAPACK CALL
  879. ELSE IF ( ABS(X(ICAMAX(M, X(1,i),1),i )) &
  880. /= ZERO ) THEN
  881. ! Y(:,i) is zero vector. If X(:,i) is not
  882. ! zero, then a warning flag is raised.
  883. ! The computation continues but the
  884. ! situation will be reported in the output.
  885. BADXY = .TRUE.
  886. END IF
  887. END DO
  888. END IF
  889. !
  890. ! <2> SVD of the data snapshot matrix X.
  891. ! =====================================
  892. ! The left singular vectors are stored in the array X.
  893. ! The right singular vectors are in the array W.
  894. ! The array W will later on contain the eigenvectors
  895. ! of a Rayleigh quotient.
  896. NUMRNK = N
  897. SELECT CASE ( WHTSVD )
  898. CASE (1)
  899. CALL CGESVD( 'O', 'S', M, N, X, LDX, RWORK, B, &
  900. LDB, W, LDW, ZWORK, LZWORK, RWORK(N+1), INFO1 ) ! LAPACK CALL
  901. T_OR_N = 'C'
  902. CASE (2)
  903. CALL CGESDD( 'O', M, N, X, LDX, RWORK, B, LDB, W, &
  904. LDW, ZWORK, LZWORK, RWORK(N+1), IWORK, INFO1 ) ! LAPACK CALL
  905. T_OR_N = 'C'
  906. CASE (3)
  907. CALL CGESVDQ( 'H', 'P', 'N', 'R', 'R', M, N, &
  908. X, LDX, RWORK, Z, LDZ, W, LDW, &
  909. NUMRNK, IWORK, LIWORK, ZWORK, &
  910. LZWORK, RWORK(N+1), LRWORK-N, INFO1) ! LAPACK CALL
  911. CALL CLACPY( 'A', M, NUMRNK, Z, LDZ, X, LDX ) ! LAPACK CALL
  912. T_OR_N = 'C'
  913. CASE (4)
  914. CALL CGEJSV( 'F', 'U', JSVOPT, 'N', 'N', 'P', M, &
  915. N, X, LDX, RWORK, Z, LDZ, W, LDW, &
  916. ZWORK, LZWORK, RWORK(N+1), LRWORK-N, IWORK, INFO1 ) ! LAPACK CALL
  917. CALL CLACPY( 'A', M, N, Z, LDZ, X, LDX ) ! LAPACK CALL
  918. T_OR_N = 'N'
  919. XSCL1 = RWORK(N+1)
  920. XSCL2 = RWORK(N+2)
  921. IF ( XSCL1 /= XSCL2 ) THEN
  922. ! This is an exceptional situation. If the
  923. ! data matrices are not scaled and the
  924. ! largest singular value of X overflows.
  925. ! In that case CGEJSV can return the SVD
  926. ! in scaled form. The scaling factor can be used
  927. ! to rescale the data (X and Y).
  928. CALL CLASCL( 'G', 0, 0, XSCL1, XSCL2, M, N, Y, LDY, INFO2 )
  929. END IF
  930. END SELECT
  931. !
  932. IF ( INFO1 > 0 ) THEN
  933. ! The SVD selected subroutine did not converge.
  934. ! Return with an error code.
  935. INFO = 2
  936. RETURN
  937. END IF
  938. !
  939. IF ( RWORK(1) == ZERO ) THEN
  940. ! The largest computed singular value of (scaled)
  941. ! X is zero. Return error code -8
  942. ! (the 8th input variable had an illegal value).
  943. K = 0
  944. INFO = -8
  945. CALL XERBLA('CGEDMD',-INFO)
  946. RETURN
  947. END IF
  948. !
  949. !<3> Determine the numerical rank of the data
  950. ! snapshots matrix X. This depends on the
  951. ! parameters NRNK and TOL.
  952. SELECT CASE ( NRNK )
  953. CASE ( -1 )
  954. K = 1
  955. DO i = 2, NUMRNK
  956. IF ( ( RWORK(i) <= RWORK(1)*TOL ) .OR. &
  957. ( RWORK(i) <= SMALL ) ) EXIT
  958. K = K + 1
  959. END DO
  960. CASE ( -2 )
  961. K = 1
  962. DO i = 1, NUMRNK-1
  963. IF ( ( RWORK(i+1) <= RWORK(i)*TOL ) .OR. &
  964. ( RWORK(i) <= SMALL ) ) EXIT
  965. K = K + 1
  966. END DO
  967. CASE DEFAULT
  968. K = 1
  969. DO i = 2, NRNK
  970. IF ( RWORK(i) <= SMALL ) EXIT
  971. K = K + 1
  972. END DO
  973. END SELECT
  974. ! Now, U = X(1:M,1:K) is the SVD/POD basis for the
  975. ! snapshot data in the input matrix X.
  976. !<4> Compute the Rayleigh quotient S = U^H * A * U.
  977. ! Depending on the requested outputs, the computation
  978. ! is organized to compute additional auxiliary
  979. ! matrices (for the residuals and refinements).
  980. !
  981. ! In all formulas below, we need V_k*Sigma_k^(-1)
  982. ! where either V_k is in W(1:N,1:K), or V_k^H is in
  983. ! W(1:K,1:N). Here Sigma_k=diag(WORK(1:K)).
  984. IF ( LSAME(T_OR_N, 'N') ) THEN
  985. DO i = 1, K
  986. CALL CSSCAL( N, ONE/RWORK(i), W(1,i), 1 ) ! BLAS CALL
  987. ! W(1:N,i) = (ONE/RWORK(i)) * W(1:N,i) ! INTRINSIC
  988. END DO
  989. ELSE
  990. ! This non-unit stride access is due to the fact
  991. ! that CGESVD, CGESVDQ and CGESDD return the
  992. ! adjoint matrix of the right singular vectors.
  993. !DO i = 1, K
  994. ! CALL DSCAL( N, ONE/RWORK(i), W(i,1), LDW ) ! BLAS CALL
  995. ! ! W(i,1:N) = (ONE/RWORK(i)) * W(i,1:N) ! INTRINSIC
  996. !END DO
  997. DO i = 1, K
  998. RWORK(N+i) = ONE/RWORK(i)
  999. END DO
  1000. DO j = 1, N
  1001. DO i = 1, K
  1002. W(i,j) = CMPLX(RWORK(N+i),ZERO,KIND=WP)*W(i,j)
  1003. END DO
  1004. END DO
  1005. END IF
  1006. !
  1007. IF ( WNTREF ) THEN
  1008. !
  1009. ! Need A*U(:,1:K)=Y*V_k*inv(diag(WORK(1:K)))
  1010. ! for computing the refined Ritz vectors
  1011. ! (optionally, outside CGEDMD).
  1012. CALL CGEMM( 'N', T_OR_N, M, K, N, ZONE, Y, LDY, W, &
  1013. LDW, ZZERO, Z, LDZ ) ! BLAS CALL
  1014. ! Z(1:M,1:K)=MATMUL(Y(1:M,1:N),TRANSPOSE(W(1:K,1:N))) ! INTRINSIC, for T_OR_N=='T'
  1015. ! Z(1:M,1:K)=MATMUL(Y(1:M,1:N),W(1:N,1:K)) ! INTRINSIC, for T_OR_N=='N'
  1016. !
  1017. ! At this point Z contains
  1018. ! A * U(:,1:K) = Y * V_k * Sigma_k^(-1), and
  1019. ! this is needed for computing the residuals.
  1020. ! This matrix is returned in the array B and
  1021. ! it can be used to compute refined Ritz vectors.
  1022. CALL CLACPY( 'A', M, K, Z, LDZ, B, LDB ) ! BLAS CALL
  1023. ! B(1:M,1:K) = Z(1:M,1:K) ! INTRINSIC
  1024. CALL CGEMM( 'C', 'N', K, K, M, ZONE, X, LDX, Z, &
  1025. LDZ, ZZERO, S, LDS ) ! BLAS CALL
  1026. ! S(1:K,1:K) = MATMUL(TANSPOSE(X(1:M,1:K)),Z(1:M,1:K)) ! INTRINSIC
  1027. ! At this point S = U^H * A * U is the Rayleigh quotient.
  1028. ELSE
  1029. ! A * U(:,1:K) is not explicitly needed and the
  1030. ! computation is organized differently. The Rayleigh
  1031. ! quotient is computed more efficiently.
  1032. CALL CGEMM( 'C', 'N', K, N, M, ZONE, X, LDX, Y, LDY, &
  1033. ZZERO, Z, LDZ ) ! BLAS CALL
  1034. ! Z(1:K,1:N) = MATMUL( TRANSPOSE(X(1:M,1:K)), Y(1:M,1:N) ) ! INTRINSIC
  1035. !
  1036. CALL CGEMM( 'N', T_OR_N, K, K, N, ZONE, Z, LDZ, W, &
  1037. LDW, ZZERO, S, LDS ) ! BLAS CALL
  1038. ! S(1:K,1:K) = MATMUL(Z(1:K,1:N),TRANSPOSE(W(1:K,1:N))) ! INTRINSIC, for T_OR_N=='T'
  1039. ! S(1:K,1:K) = MATMUL(Z(1:K,1:N),(W(1:N,1:K))) ! INTRINSIC, for T_OR_N=='N'
  1040. ! At this point S = U^H * A * U is the Rayleigh quotient.
  1041. ! If the residuals are requested, save scaled V_k into Z.
  1042. ! Recall that V_k or V_k^H is stored in W.
  1043. IF ( WNTRES .OR. WNTEX ) THEN
  1044. IF ( LSAME(T_OR_N, 'N') ) THEN
  1045. CALL CLACPY( 'A', N, K, W, LDW, Z, LDZ )
  1046. ELSE
  1047. CALL CLACPY( 'A', K, N, W, LDW, Z, LDZ )
  1048. END IF
  1049. END IF
  1050. END IF
  1051. !
  1052. !<5> Compute the Ritz values and (if requested) the
  1053. ! right eigenvectors of the Rayleigh quotient.
  1054. !
  1055. CALL CGEEV( 'N', JOBZL, K, S, LDS, EIGS, W, &
  1056. LDW, W, LDW, ZWORK, LZWORK, RWORK(N+1), INFO1 ) ! LAPACK CALL
  1057. !
  1058. ! W(1:K,1:K) contains the eigenvectors of the Rayleigh
  1059. ! quotient. See the description of Z.
  1060. ! Also, see the description of CGEEV.
  1061. IF ( INFO1 > 0 ) THEN
  1062. ! CGEEV failed to compute the eigenvalues and
  1063. ! eigenvectors of the Rayleigh quotient.
  1064. INFO = 3
  1065. RETURN
  1066. END IF
  1067. !
  1068. ! <6> Compute the eigenvectors (if requested) and,
  1069. ! the residuals (if requested).
  1070. !
  1071. IF ( WNTVEC .OR. WNTEX ) THEN
  1072. IF ( WNTRES ) THEN
  1073. IF ( WNTREF ) THEN
  1074. ! Here, if the refinement is requested, we have
  1075. ! A*U(:,1:K) already computed and stored in Z.
  1076. ! For the residuals, need Y = A * U(:,1;K) * W.
  1077. CALL CGEMM( 'N', 'N', M, K, K, ZONE, Z, LDZ, W, &
  1078. LDW, ZZERO, Y, LDY ) ! BLAS CALL
  1079. ! Y(1:M,1:K) = Z(1:M,1:K) * W(1:K,1:K) ! INTRINSIC
  1080. ! This frees Z; Y contains A * U(:,1:K) * W.
  1081. ELSE
  1082. ! Compute S = V_k * Sigma_k^(-1) * W, where
  1083. ! V_k * Sigma_k^(-1) (or its adjoint) is stored in Z
  1084. CALL CGEMM( T_OR_N, 'N', N, K, K, ZONE, Z, LDZ, &
  1085. W, LDW, ZZERO, S, LDS)
  1086. ! Then, compute Z = Y * S =
  1087. ! = Y * V_k * Sigma_k^(-1) * W(1:K,1:K) =
  1088. ! = A * U(:,1:K) * W(1:K,1:K)
  1089. CALL CGEMM( 'N', 'N', M, K, N, ZONE, Y, LDY, S, &
  1090. LDS, ZZERO, Z, LDZ)
  1091. ! Save a copy of Z into Y and free Z for holding
  1092. ! the Ritz vectors.
  1093. CALL CLACPY( 'A', M, K, Z, LDZ, Y, LDY )
  1094. IF ( WNTEX ) CALL CLACPY( 'A', M, K, Z, LDZ, B, LDB )
  1095. END IF
  1096. ELSE IF ( WNTEX ) THEN
  1097. ! Compute S = V_k * Sigma_k^(-1) * W, where
  1098. ! V_k * Sigma_k^(-1) is stored in Z
  1099. CALL CGEMM( T_OR_N, 'N', N, K, K, ZONE, Z, LDZ, &
  1100. W, LDW, ZZERO, S, LDS)
  1101. ! Then, compute Z = Y * S =
  1102. ! = Y * V_k * Sigma_k^(-1) * W(1:K,1:K) =
  1103. ! = A * U(:,1:K) * W(1:K,1:K)
  1104. CALL CGEMM( 'N', 'N', M, K, N, ZONE, Y, LDY, S, &
  1105. LDS, ZZERO, B, LDB)
  1106. ! The above call replaces the following two calls
  1107. ! that were used in the developing-testing phase.
  1108. ! CALL CGEMM( 'N', 'N', M, K, N, ZONE, Y, LDY, S, &
  1109. ! LDS, ZZERO, Z, LDZ)
  1110. ! Save a copy of Z into Y and free Z for holding
  1111. ! the Ritz vectors.
  1112. ! CALL CLACPY( 'A', M, K, Z, LDZ, B, LDB )
  1113. END IF
  1114. !
  1115. ! Compute the Ritz vectors
  1116. IF ( WNTVEC ) CALL CGEMM( 'N', 'N', M, K, K, ZONE, X, LDX, W, LDW, &
  1117. ZZERO, Z, LDZ ) ! BLAS CALL
  1118. ! Z(1:M,1:K) = MATMUL(X(1:M,1:K), W(1:K,1:K)) ! INTRINSIC
  1119. !
  1120. IF ( WNTRES ) THEN
  1121. DO i = 1, K
  1122. CALL CAXPY( M, -EIGS(i), Z(1,i), 1, Y(1,i), 1 ) ! BLAS CALL
  1123. ! Y(1:M,i) = Y(1:M,i) - EIGS(i) * Z(1:M,i) ! INTRINSIC
  1124. RES(i) = SCNRM2( M, Y(1,i), 1) ! BLAS CALL
  1125. END DO
  1126. END IF
  1127. END IF
  1128. !
  1129. IF ( WHTSVD == 4 ) THEN
  1130. RWORK(N+1) = XSCL1
  1131. RWORK(N+2) = XSCL2
  1132. END IF
  1133. !
  1134. ! Successful exit.
  1135. IF ( .NOT. BADXY ) THEN
  1136. INFO = 0
  1137. ELSE
  1138. ! A warning on possible data inconsistency.
  1139. ! This should be a rare event.
  1140. INFO = 4
  1141. END IF
  1142. !............................................................
  1143. RETURN
  1144. ! ......
  1145. END SUBROUTINE CGEDMD