root / src / Step_DIIS.f90 @ 12
Historique | Voir | Annoter | Télécharger (11,77 ko)
1 | 1 | pfleura2 | !C HEAT is never used, not even in call of Space(...) |
---|---|---|---|
2 | 1 | pfleura2 | !C XPARAM = input parameter vector (Geometry). |
3 | 1 | pfleura2 | !C Grad = input gradient vector. |
4 | 1 | pfleura2 | SUBROUTINE Step_DIIS(XP,XPARAM,GP,GRAD,HP,HEAT,Hess,NVAR,FRST) |
5 | 12 | pfleura2 | |
6 | 12 | pfleura2 | !---------------------------------------------------------------------- |
7 | 12 | pfleura2 | ! This routine was adapted from the public domain mopac6 diis.f |
8 | 12 | pfleura2 | ! source file (c) 2009, Stewart Computational Chemistry. |
9 | 12 | pfleura2 | ! <http://www.openmopac.net/Downloads/Downloads.html> |
10 | 12 | pfleura2 | ! |
11 | 12 | pfleura2 | !---------------------------------------------------------------------- |
12 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
13 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
14 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
15 | 12 | pfleura2 | ! |
16 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
17 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
18 | 12 | pfleura2 | ! |
19 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
20 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
21 | 12 | pfleura2 | ! |
22 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
23 | 12 | pfleura2 | ! |
24 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
25 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
26 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
27 | 12 | pfleura2 | ! or (at your option) any later version. |
28 | 12 | pfleura2 | ! |
29 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
30 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
31 | 12 | pfleura2 | ! |
32 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
33 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
34 | 12 | pfleura2 | ! |
35 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
36 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
37 | 12 | pfleura2 | ! |
38 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
39 | 12 | pfleura2 | ! for commercial licensing opportunities. |
40 | 12 | pfleura2 | !---------------------------------------------------------------------- |
41 | 12 | pfleura2 | |
42 | 1 | pfleura2 | IMPLICIT NONE |
43 | 1 | pfleura2 | integer, parameter :: KINT = kind(1) |
44 | 1 | pfleura2 | integer, parameter :: KREAL = kind(1.0d0) |
45 | 1 | pfleura2 | |
46 | 1 | pfleura2 | ! INCLUDE 'SIZES' |
47 | 1 | pfleura2 | |
48 | 1 | pfleura2 | INTEGER(KINT) :: NVAR |
49 | 1 | pfleura2 | REAL(KREAL) :: XP(NVAR), XPARAM(NVAR), GP(NVAR), GRAD(NVAR), Hess(NVAR*NVAR) |
50 | 1 | pfleura2 | !REAL(KREAL) :: Hess_inv(NVAR,NVAR),XPARAM_old(NVAR),STEP(NVAR) |
51 | 1 | pfleura2 | REAL(KREAL) :: HEAT, HP |
52 | 1 | pfleura2 | LOGICAL :: FRST |
53 | 1 | pfleura2 | |
54 | 1 | pfleura2 | !************************************************************************ |
55 | 1 | pfleura2 | !* * |
56 | 1 | pfleura2 | !* DIIS PERFORMS DIRECT INVERSION IN THE ITERATIVE SUBSPACE * |
57 | 1 | pfleura2 | !* * |
58 | 1 | pfleura2 | !* THIS INVOLVES SOLVING FOR C IN XPARAM(NEW) = XPARAM' - HG' * |
59 | 1 | pfleura2 | !* * |
60 | 1 | pfleura2 | !* WHERE XPARAM' = SUM(C(I)XPARAM(I), THE C COEFFICIENTES COMING FROM * |
61 | 1 | pfleura2 | !* * |
62 | 1 | pfleura2 | !* | B 1 | . | C | = | 0 | * |
63 | 1 | pfleura2 | !* | 1 0 | |-L | | 1 | * |
64 | 1 | pfleura2 | !* * |
65 | 1 | pfleura2 | !* WHERE B(I,J) =GRAD(I)H(T)HGRAD(J) GRAD(I) = GRADIENT ON CYCLE I * |
66 | 1 | pfleura2 | !* Hess = INVERSE HESSIAN * |
67 | 1 | pfleura2 | !* * |
68 | 1 | pfleura2 | !* REFERENCE * |
69 | 1 | pfleura2 | !* * |
70 | 1 | pfleura2 | !* P. CSASZAR, P. PULAY, J. MOL. STRUCT. (THEOCHEM), 114, 31 (1984) * |
71 | 1 | pfleura2 | !* * |
72 | 1 | pfleura2 | !************************************************************************ |
73 | 1 | pfleura2 | !************************************************************************ |
74 | 1 | pfleura2 | !* * |
75 | 1 | pfleura2 | !* GEOMETRY OPTIMIZATION USING THE METHOD OF DIRECT INVERSION IN * |
76 | 1 | pfleura2 | !* THE ITERATIVE SUBSPACE (GDIIS), COMBINED WITH THE BFGS OPTIMIZER * |
77 | 1 | pfleura2 | !* (A VARIABLE METRIC METHOD) * |
78 | 1 | pfleura2 | !* * |
79 | 1 | pfleura2 | !* WRITTEN BY PETER L. CUMMINS, UNIVERSITY OF SYDNEY, AUSTRALIA * |
80 | 1 | pfleura2 | !* * |
81 | 1 | pfleura2 | !* REFERENCE * |
82 | 1 | pfleura2 | !* * |
83 | 1 | pfleura2 | !* "COMPUTATIONAL STRATEGIES FOR THE OPTIMIZATION OF EQUILIBRIUM * |
84 | 1 | pfleura2 | !* GEOMETRIES AND TRANSITION-STATE STRUCTURES AT THE SEMIEMPIRICAL * |
85 | 1 | pfleura2 | !* LEVEL", PETER L. CUMMINS, JILL E. GREADY, J. COMP. CHEM., 10, * |
86 | 1 | pfleura2 | !* 939-950 (1989). * |
87 | 1 | pfleura2 | !* * |
88 | 1 | pfleura2 | !* MODIFIED BY JJPS TO CONFORM TO EXISTING MOPAC CONVENTIONS * |
89 | 1 | pfleura2 | !* * |
90 | 1 | pfleura2 | !************************************************************************ |
91 | 1 | pfleura2 | |
92 | 1 | pfleura2 | ! MRESET = number of iterations. |
93 | 1 | pfleura2 | INTEGER(KINT), PARAMETER :: MRESET=15, M2=(MRESET+1)*(MRESET+1) !M2 = 256 |
94 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE, SAVE :: XSET(:),GSET(:),ERR(:) ! MRESET*NVAR |
95 | 1 | pfleura2 | REAL(KREAL) :: ESET(MRESET) |
96 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE, SAVE :: DX(:),GSAVE(:) !NVAR |
97 | 2 | pfleura2 | REAL(KREAL) :: B(M2), BS(M2) |
98 | 1 | pfleura2 | LOGICAL DEBUG, PRINT |
99 | 1 | pfleura2 | INTEGER(KINT), SAVE :: MSET |
100 | 1 | pfleura2 | INTEGER(KINT) :: NDIIS, MPLUS, INV, ITERA, MM |
101 | 1 | pfleura2 | INTEGER(KINT) :: I,J,K, JJ, KJ, JNV, II, IONE, IJ, INK,ITmp |
102 | 1 | pfleura2 | REAL(KREAL) :: XMax, XNorm, S, DET, THRES |
103 | 1 | pfleura2 | |
104 | 1 | pfleura2 | DEBUG=.TRUE. |
105 | 1 | pfleura2 | PRINT=.TRUE. |
106 | 1 | pfleura2 | |
107 | 1 | pfleura2 | IF (PRINT) WRITE(*,'(/,'' BEGIN GDIIS '')') |
108 | 1 | pfleura2 | |
109 | 1 | pfleura2 | !XPARAM_old = XPARAM |
110 | 1 | pfleura2 | |
111 | 1 | pfleura2 | ! Initialization |
112 | 1 | pfleura2 | IF (FRST) THEN |
113 | 1 | pfleura2 | ! FRST will be set to False in Space, so no need to modify it here |
114 | 1 | pfleura2 | IF (ALLOCATED(XSET)) THEN |
115 | 1 | pfleura2 | IF (PRINT) WRITE(*,'(/,'' In FRST, GDIIS Dealloc '')') |
116 | 1 | pfleura2 | DEALLOCATE(XSet,GSET,ERR,DX,GSave) |
117 | 1 | pfleura2 | RETURN |
118 | 1 | pfleura2 | ELSE |
119 | 1 | pfleura2 | IF (PRINT) WRITE(*,'(/,'' In FRST, GDIIS alloc '')') |
120 | 1 | pfleura2 | ALLOCATE(XSet(MRESET*NVAR), GSet(MRESET*NVAR), ERR(MRESET*NVAR)) |
121 | 1 | pfleura2 | ALLOCATE(DX(NVAR),GSAVE(NVAR)) |
122 | 1 | pfleura2 | END IF |
123 | 1 | pfleura2 | END IF |
124 | 1 | pfleura2 | !C |
125 | 1 | pfleura2 | !C SPACE SIMPLY LOADS THE CURRENT VALUES OF XPARAM AND GRAD INTO |
126 | 1 | pfleura2 | !C THE ARRAYS XSET AND GSET |
127 | 1 | pfleura2 | !C |
128 | 1 | pfleura2 | !C HEAT is never used, not even in Space(...) |
129 | 1 | pfleura2 | CALL SPACE(MRESET,MSET,XPARAM,GRAD,HEAT,NVAR,XSET,GSET,ESET,FRST) |
130 | 1 | pfleura2 | |
131 | 1 | pfleura2 | IF (PRINT) WRITE(*,'(/,'' GDIIS after Space '')') |
132 | 1 | pfleura2 | |
133 | 1 | pfleura2 | ! INITIALIZE SOME VARIABLES AND CONSTANTS: |
134 | 1 | pfleura2 | NDIIS = MSET |
135 | 1 | pfleura2 | MPLUS = MSET + 1 |
136 | 1 | pfleura2 | MM = MPLUS * MPLUS |
137 | 1 | pfleura2 | |
138 | 1 | pfleura2 | ! COMPUTE THE APPROXIMATE ERROR VECTORS: |
139 | 1 | pfleura2 | INV=-NVAR |
140 | 1 | pfleura2 | DO 30 I=1,MSET |
141 | 1 | pfleura2 | INV = INV + NVAR |
142 | 1 | pfleura2 | DO 30 J=1,NVAR |
143 | 1 | pfleura2 | S = 0.D0 |
144 | 1 | pfleura2 | KJ=(J*(J-1))/2 |
145 | 1 | pfleura2 | DO 10 K=1,J |
146 | 1 | pfleura2 | KJ = KJ+1 |
147 | 1 | pfleura2 | 10 S = S - Hess(KJ) * GSET(INV+K) |
148 | 1 | pfleura2 | DO 20 K=J+1,NVAR |
149 | 1 | pfleura2 | KJ = (K*(K-1))/2+J |
150 | 1 | pfleura2 | 20 S = S - Hess(KJ) * GSET(INV+K) |
151 | 1 | pfleura2 | 30 ERR(INV+J) = S |
152 | 1 | pfleura2 | |
153 | 1 | pfleura2 | |
154 | 1 | pfleura2 | |
155 | 1 | pfleura2 | ! CONSTRUCT THE GDIIS MATRIX: |
156 | 1 | pfleura2 | ! initialization (not really needed) |
157 | 1 | pfleura2 | DO I=1,MM |
158 | 1 | pfleura2 | B(I) = 1.D0 |
159 | 1 | pfleura2 | END DO |
160 | 1 | pfleura2 | |
161 | 1 | pfleura2 | ! B_ij calculations from <e_i|e_j> |
162 | 1 | pfleura2 | JJ=0 |
163 | 1 | pfleura2 | INV=-NVAR |
164 | 1 | pfleura2 | DO 50 I=1,MSET |
165 | 1 | pfleura2 | INV=INV+NVAR |
166 | 1 | pfleura2 | JNV=-NVAR |
167 | 1 | pfleura2 | DO 50 J=1,MSET |
168 | 1 | pfleura2 | JNV=JNV+NVAR |
169 | 1 | pfleura2 | JJ = JJ + 1 |
170 | 1 | pfleura2 | B(JJ)=0.D0 |
171 | 1 | pfleura2 | DO 50 K=1,NVAR |
172 | 1 | pfleura2 | 50 B(JJ) = B(JJ) + ERR(INV+K) * ERR(JNV+K) |
173 | 1 | pfleura2 | |
174 | 1 | pfleura2 | ! The following shifting is required to correct indices of B_ij elements in the GDIIS matrix. |
175 | 1 | pfleura2 | ! The correction is needed because the last coloumn of the matrix contains all 1 and one zero. |
176 | 1 | pfleura2 | DO 60 I=MSET-1,1,-1 |
177 | 1 | pfleura2 | DO 60 J=MSET,1,-1 |
178 | 1 | pfleura2 | 60 B(I*MSET+J+I) = B(I*MSET+J) |
179 | 1 | pfleura2 | |
180 | 1 | pfleura2 | ! For last row and last column of GDIIS matrix |
181 | 1 | pfleura2 | DO 70 I=1,MPLUS |
182 | 1 | pfleura2 | B(MPLUS*I) = 1.D0 |
183 | 1 | pfleura2 | 70 B(MPLUS*MSET+I) = 1.D0 |
184 | 1 | pfleura2 | B(MM) = 0.D0 |
185 | 1 | pfleura2 | |
186 | 1 | pfleura2 | ! ELIMINATE ERROR VECTORS WITH THE LARGEST NORM: |
187 | 1 | pfleura2 | 80 CONTINUE |
188 | 1 | pfleura2 | DO 90 I=1,MM |
189 | 1 | pfleura2 | 90 BS(I) = B(I) |
190 | 1 | pfleura2 | IF (NDIIS .EQ. MSET) GO TO 140 |
191 | 1 | pfleura2 | DO 130 II=1,MSET-NDIIS |
192 | 1 | pfleura2 | XMAX = -1.D10 |
193 | 1 | pfleura2 | ITERA = 0 |
194 | 1 | pfleura2 | DO 110 I=1,MSET |
195 | 1 | pfleura2 | XNORM = 0.D0 |
196 | 1 | pfleura2 | INV = (I-1) * MPLUS |
197 | 1 | pfleura2 | DO 100 J=1,MSET |
198 | 1 | pfleura2 | 100 XNORM = XNORM + ABS(B(INV + J)) |
199 | 1 | pfleura2 | IF (XMAX.LT.XNORM .AND. XNORM.NE.1.0D0) THEN |
200 | 1 | pfleura2 | XMAX = XNORM |
201 | 1 | pfleura2 | ITERA = I |
202 | 1 | pfleura2 | IONE = INV + I |
203 | 1 | pfleura2 | ENDIF |
204 | 1 | pfleura2 | 110 CONTINUE |
205 | 1 | pfleura2 | DO 120 I=1,MPLUS |
206 | 1 | pfleura2 | INV = (I-1) * MPLUS |
207 | 1 | pfleura2 | DO 120 J=1,MPLUS |
208 | 1 | pfleura2 | JNV = (J-1) * MPLUS |
209 | 1 | pfleura2 | IF (J.EQ.ITERA) B(INV + J) = 0.D0 |
210 | 1 | pfleura2 | B(JNV + I) = B(INV + J) |
211 | 1 | pfleura2 | 120 CONTINUE |
212 | 1 | pfleura2 | B(IONE) = 1.0D0 |
213 | 1 | pfleura2 | 130 CONTINUE |
214 | 1 | pfleura2 | 140 CONTINUE |
215 | 1 | pfleura2 | |
216 | 1 | pfleura2 | IF (DEBUG) THEN |
217 | 1 | pfleura2 | |
218 | 1 | pfleura2 | ! OUTPUT THE GDIIS MATRIX: |
219 | 1 | pfleura2 | WRITE(*,'(/5X,'' GDIIS MATRIX'')') |
220 | 1 | pfleura2 | ITmp=min(12,MPLUS) |
221 | 1 | pfleura2 | DO IJ=1,MPLUS |
222 | 1 | pfleura2 | WRITE(*,'(12(F10.4,1X))') B((IJ-1)*MPLUS+1:(IJ-1)*MPLUS+ITmp) |
223 | 1 | pfleura2 | END DO |
224 | 1 | pfleura2 | ENDIF |
225 | 1 | pfleura2 | |
226 | 1 | pfleura2 | ! SCALE DIIS MATRIX BEFORE INVERSION: |
227 | 1 | pfleura2 | |
228 | 1 | pfleura2 | DO I=1,MPLUS |
229 | 1 | pfleura2 | II = MPLUS * (I-1) + I |
230 | 1 | pfleura2 | GSAVE(I) = 1.D0 / DSQRT(1.D-20+DABS(B(II))) |
231 | 1 | pfleura2 | END DO |
232 | 1 | pfleura2 | |
233 | 1 | pfleura2 | GSAVE(MPLUS) = 1.D0 |
234 | 1 | pfleura2 | DO I=1,MPLUS |
235 | 1 | pfleura2 | DO J=1,MPLUS |
236 | 1 | pfleura2 | IJ = MPLUS * (I-1) + J |
237 | 1 | pfleura2 | B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J) |
238 | 1 | pfleura2 | END DO |
239 | 1 | pfleura2 | END DO |
240 | 1 | pfleura2 | |
241 | 1 | pfleura2 | IF (DEBUG) THEN |
242 | 1 | pfleura2 | ! OUTPUT SCALED GDIIS MATRIX: |
243 | 1 | pfleura2 | WRITE(*,'(/5X,'' GDIIS MATRIX (SCALED)'')') |
244 | 1 | pfleura2 | ITmp=min(12,MPLUS) |
245 | 1 | pfleura2 | DO IJ=1,MPLUS |
246 | 1 | pfleura2 | WRITE(*,'(12(F10.4,1X))') B((IJ-1)*MPLUS+1:(IJ-1)*MPLUS+ITmp) |
247 | 1 | pfleura2 | END DO |
248 | 1 | pfleura2 | |
249 | 1 | pfleura2 | ENDIF ! matches IF (DEBUG) THEN |
250 | 1 | pfleura2 | |
251 | 1 | pfleura2 | ! INVERT THE GDIIS MATRIX B: |
252 | 1 | pfleura2 | CALL MINV(B,MPLUS,DET) ! matrix inversion. |
253 | 1 | pfleura2 | |
254 | 1 | pfleura2 | DO I=1,MPLUS |
255 | 1 | pfleura2 | DO J=1,MPLUS |
256 | 1 | pfleura2 | IJ = MPLUS * (I-1) + J |
257 | 1 | pfleura2 | B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J) |
258 | 1 | pfleura2 | END DO |
259 | 1 | pfleura2 | END DO |
260 | 1 | pfleura2 | |
261 | 1 | pfleura2 | ! COMPUTE THE INTERMEDIATE INTERPOLATED PARAMETER AND GRADIENT VECTORS: |
262 | 1 | pfleura2 | DO K=1,NVAR |
263 | 1 | pfleura2 | XP(K) = 0.D0 |
264 | 1 | pfleura2 | GP(K) = 0.D0 |
265 | 1 | pfleura2 | DO I=1,MSET |
266 | 1 | pfleura2 | INK = (I-1) * NVAR + K |
267 | 1 | pfleura2 | !Print *, 'B(',MPLUS*MSET+I,')=', B(MPLUS*MSET+I) |
268 | 1 | pfleura2 | XP(K) = XP(K) + B(MPLUS*MSET+I) * XSET(INK) |
269 | 1 | pfleura2 | GP(K) = GP(K) + B(MPLUS*MSET+I) * GSET(INK) |
270 | 1 | pfleura2 | END DO |
271 | 1 | pfleura2 | END DO |
272 | 1 | pfleura2 | |
273 | 1 | pfleura2 | HP=0.D0 |
274 | 1 | pfleura2 | DO I=1,MSET |
275 | 1 | pfleura2 | HP=HP+B(MPLUS*MSET+I)*ESET(I) |
276 | 1 | pfleura2 | END DO |
277 | 1 | pfleura2 | |
278 | 1 | pfleura2 | DO K=1,NVAR |
279 | 1 | pfleura2 | DX(K) = XPARAM(K) - XP(K) |
280 | 1 | pfleura2 | END DO |
281 | 1 | pfleura2 | XNORM = SQRT(DOT_PRODUCT(DX,DX)) |
282 | 1 | pfleura2 | IF (PRINT) THEN |
283 | 1 | pfleura2 | WRITE (6,'(/10X,''DEVIATION IN X '',F7.4,8X,''DETERMINANT '',G9.3)') XNORM,DET |
284 | 1 | pfleura2 | WRITE(*,'(10X,''GDIIS COEFFICIENTS'')') |
285 | 1 | pfleura2 | WRITE(*,'(10X,5F12.5)') (B(MPLUS*MSET+I),I=1,MSET) |
286 | 1 | pfleura2 | ENDIF |
287 | 1 | pfleura2 | |
288 | 1 | pfleura2 | ! THE FOLLOWING TOLERENCES FOR XNORM AND DET ARE SOMEWHAT ARBITRARY! |
289 | 1 | pfleura2 | THRES = MAX(10.D0**(-NVAR), 1.D-25) |
290 | 1 | pfleura2 | IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN |
291 | 1 | pfleura2 | IF (PRINT)THEN |
292 | 1 | pfleura2 | WRITE(*,*) "THE DIIS MATRIX IS ILL CONDITIONED" |
293 | 1 | pfleura2 | WRITE(*,*) " - PROBABLY, VECTORS ARE LINEARLY DEPENDENT - " |
294 | 1 | pfleura2 | WRITE(*,*) "THE DIIS STEP WILL BE REPEATED WITH A SMALLER SPACE" |
295 | 1 | pfleura2 | END IF |
296 | 1 | pfleura2 | DO K=1,MM |
297 | 1 | pfleura2 | B(K) = BS(K) |
298 | 1 | pfleura2 | END DO |
299 | 1 | pfleura2 | NDIIS = NDIIS - 1 |
300 | 1 | pfleura2 | IF (NDIIS .GT. 0) GO TO 80 |
301 | 1 | pfleura2 | IF (PRINT) WRITE(*,'(10X,''NEWTON-RAPHSON STEP TAKEN'')') |
302 | 1 | pfleura2 | DO K=1,NVAR |
303 | 1 | pfleura2 | XP(K) = XPARAM(K) |
304 | 1 | pfleura2 | GP(K) = GRAD(K) |
305 | 1 | pfleura2 | END DO |
306 | 1 | pfleura2 | ENDIF ! matches IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN |
307 | 1 | pfleura2 | |
308 | 1 | pfleura2 | ! q_{m+1} = q'_{m+1} - H^{-1}g'_{m+1} |
309 | 1 | pfleura2 | ! Hess is a symmetric matrix. |
310 | 1 | pfleura2 | !Hess_inv = 1.d0 ! to be deleted. |
311 | 1 | pfleura2 | !Call GenInv(NVAR,Reshape(Hess,(/NVAR,NVAR/)),Hess_inv,NVAR) ! Implemented in Mat_util.f90 |
312 | 1 | pfleura2 | ! H^{-1}g'_{m+1} |
313 | 1 | pfleura2 | !Print *, 'Hess_inv=' |
314 | 1 | pfleura2 | !Print *, Hess_inv |
315 | 1 | pfleura2 | !XPARAM=0.d0 |
316 | 1 | pfleura2 | !DO I=1, NVAR |
317 | 1 | pfleura2 | !XPARAM(:) = XPARAM(:) + Hess_inv(:,I)*GP(I) |
318 | 1 | pfleura2 | !END DO |
319 | 1 | pfleura2 | !XPARAM(:) = XP(:) - XPARAM(:) ! now XPARAM is a new geometry. |
320 | 1 | pfleura2 | |
321 | 1 | pfleura2 | !STEP is the difference between the new and old geometry and thus "step": |
322 | 1 | pfleura2 | !STEP = XPARAM - XPARAM_old |
323 | 1 | pfleura2 | |
324 | 1 | pfleura2 | IF (PRINT) WRITE(*,'(/,'' END GDIIS '',/)') |
325 | 1 | pfleura2 | |
326 | 1 | pfleura2 | END SUBROUTINE Step_DIIS |