root / src / Step_DIIS_all.f90 @ 2
Historique | Voir | Annoter | Télécharger (16,19 ko)
1 |
!C HEAT is never used, not even in call of Space(...) |
---|---|
2 |
!C Geom = input parameter vector (Geometry). |
3 |
!C Grad = input gradient vector. |
4 |
!C Geom_new = New Geometry. |
5 |
|
6 |
SUBROUTINE Step_diis_all(NGeomF,IGeom,Step,Geom,Grad,HP,HEAT,Hess,NCoord,allocation_flag,Tangent) |
7 |
! IMPLICIT DOUBLE PRECISION (A-H,O-Z) |
8 |
|
9 |
USE Io_module, only : IoOut |
10 |
USE Path_module, only : Vfree |
11 |
|
12 |
IMPLICIT NONE |
13 |
INTEGER, parameter :: KINT = kind(1) |
14 |
INTEGER, parameter :: KREAL = kind(1.0d0) |
15 |
|
16 |
! INCLUDE 'SIZES' |
17 |
|
18 |
INTEGER(KINT) :: NGeomF,IGeom |
19 |
REAL(KREAL) :: Geom_new(NCoord),Geom(NCoord),Grad(NCoord) |
20 |
REAL(KREAL) :: Hess(NCoord*NCoord),Step(NCoord) |
21 |
REAL(KREAL) :: HEAT,HP |
22 |
LOGICAL :: allocation_flag |
23 |
INTEGER(KINT), INTENT(IN) :: NCoord |
24 |
REAL(KREAL), INTENT(INOUT) :: Tangent(Ncoord) |
25 |
|
26 |
!************************************************************************ |
27 |
!* * |
28 |
!* DIIS PERFORMS DIRECT INVERSION IN THE ITERATIVE SUBSPACE * |
29 |
!* * |
30 |
!* THIS INVOLVES SOLVING FOR C IN Geom(NEW) = Geom' - HG' * |
31 |
!* * |
32 |
!* WHERE Geom' = SUM(C(I)Geom(I), THE C COEFFICIENTES COMING FROM * |
33 |
!* * |
34 |
!* | B 1 | . | C | = | 0 | * |
35 |
!* | 1 0 | |-L | | 1 | * |
36 |
!* * |
37 |
!* WHERE B(I,J) =GRAD(I)H(T)HGRAD(J) GRAD(I) = GRADIENT ON CYCLE I * |
38 |
!* Hess = INVERSE HESSIAN * |
39 |
!* * |
40 |
!* REFERENCE * |
41 |
!* * |
42 |
!* P. CSASZAR, P. PULAY, J. MOL. STRUCT. (THEOCHEM), 114, 31 (1984) * |
43 |
!* * |
44 |
!************************************************************************ |
45 |
!************************************************************************ |
46 |
!* * |
47 |
!* GEOMETRY OPTIMIZATION USING THE METHOD OF DIRECT INVERSION IN * |
48 |
!* THE ITERATIVE SUBSPACE (GDIIS), COMBINED WITH THE BFGS OPTIMIZER * |
49 |
!* (A VARIABLE METRIC METHOD) * |
50 |
!* * |
51 |
!* WRITTEN BY PETER L. CUMMINS, UNIVERSITY OF SYDNEY, AUSTRALIA * |
52 |
!* * |
53 |
!* REFERENCE * |
54 |
!* * |
55 |
!* "COMPUTATIONAL STRATEGIES FOR THE OPTIMIZATION OF EQUILIBRIUM * |
56 |
!* GEOMETRIES AND TRANSITION-STATE STRUCTURES AT THE SEMIEMPIRICAL * |
57 |
!* LEVEL", PETER L. CUMMINS, JILL E. GREADY, J. COMP. CHEM., 10, * |
58 |
!* 939-950 (1989). * |
59 |
!* * |
60 |
!* MODIFIED BY JJPS TO CONFORM TO EXISTING MOPAC CONVENTIONS * |
61 |
!* * |
62 |
!************************************************************************ |
63 |
|
64 |
! MRESET = maximum number of iterations. |
65 |
INTEGER(KINT), PARAMETER :: MRESET=15, M2=(MRESET+1)*(MRESET+1) !M2 = 256 |
66 |
REAL(KREAL), ALLOCATABLE, SAVE :: GeomSet(:,:),GradSet(:,:),ERR(:,:) ! MRESET*NCoord |
67 |
REAL(KREAL), SAVE :: ESET(MRESET) |
68 |
REAL(KREAL), ALLOCATABLE, SAVE :: DXTMP(:,:),GSAVE(:,:) !NCoord, why DXTMP has SAVE attribute?? |
69 |
REAL(KREAL) :: B(M2),BS(M2),BST(M2) |
70 |
LOGICAL DEBUG, PRINT |
71 |
INTEGER(KINT), ALLOCATABLE, SAVE :: MSET(:) |
72 |
LOGICAL, ALLOCATABLE, SAVE :: FRST(:) |
73 |
INTEGER(KINT) :: NDIIS, MPLUS, INV, ITERA, MM, NFree, I, J, K |
74 |
INTEGER(KINT) :: JJ, KJ, JNV, II, IONE, IJ, INK,ITmp, Isch, Idx |
75 |
REAL(KREAL) :: XMax, XNorm, S, DET, THRES, Norm |
76 |
REAL(KREAL), PARAMETER :: eps=1e-12 |
77 |
REAL(KREAL), PARAMETER :: crit=1e-8 |
78 |
REAL(KREAL), ALLOCATABLE :: Tanf(:) ! NCoord |
79 |
REAL(KREAL), ALLOCATABLE :: HFree(:) ! NFree*NFree |
80 |
REAL(KREAL), ALLOCATABLE :: Htmp(:,:) ! NCoord,NFree |
81 |
REAL(KREAL), ALLOCATABLE :: Grad_free(:),Grad_new_free_inter(:),Step_free(:) ! NFree |
82 |
REAL(KREAL), ALLOCATABLE :: Geom_free(:),Geom_new_free_inter(:),Geom_new_free(:) ! NFree |
83 |
REAL(KREAL), ALLOCATABLE, SAVE :: GeomSet_free(:,:),GradSet_free(:,:) |
84 |
|
85 |
DEBUG=.TRUE. |
86 |
PRINT=.TRUE. |
87 |
|
88 |
IF (PRINT) WRITE(*,'(/,'' BEGIN GDIIS '')') |
89 |
|
90 |
! Initialization |
91 |
IF (allocation_flag) THEN ! allocation_flag = .TRUE. at the begining and effective for all geometries in path. |
92 |
! FRST(IGeom) will be set to False in Space, so no need to modify it here |
93 |
IF (ALLOCATED(GeomSet)) THEN |
94 |
IF (PRINT) WRITE(*,'(/,'' In FRST, GDIIS Dealloc '')') |
95 |
DEALLOCATE(GeomSet,GradSet,ERR,DXTMP,GSave,GeomSet_free,GradSet_free) |
96 |
RETURN |
97 |
ELSE |
98 |
! these allocated arrays need to be properly deallocated. |
99 |
IF (PRINT) WRITE(*,'(/,'' In FRST, GDIIS Alloc '')') |
100 |
ALLOCATE(GeomSet(NGeomF,MRESET*NCoord),GradSet(NGeomF,MRESET*NCoord),ERR(NGeomF,MRESET*NCoord)) |
101 |
ALLOCATE(GeomSet_free(NGeomF,MRESET*NCoord),GradSet_free(NGeomF,MRESET*NCoord)) |
102 |
ALLOCATE(DXTMP(NGeomF,NCoord),GSAVE(NGeomF,NCoord),MSET(NGeomF),FRST(NGeomF)) |
103 |
DO I=1,NGeomF |
104 |
FRST(I) = .TRUE. |
105 |
GeomSet(I,:) = 0.d0 |
106 |
GradSet(I,:) = 0.d0 |
107 |
ERR(I,:) = 0.d0 |
108 |
GeomSet_free(I,:) = 0.d0 |
109 |
GradSet_free(I,:) = 0.d0 |
110 |
DXTMP(I,:)=0.d0 |
111 |
GSAVE(I,:)=0.d0 |
112 |
END DO |
113 |
MSET(:)=0 |
114 |
END IF |
115 |
allocation_flag = .FALSE. |
116 |
END IF |
117 |
|
118 |
! Addded from here: |
119 |
Call FreeMv(NCoord,Vfree) ! VFree(Ncoord,Ncoord) |
120 |
! we orthogonalize Vfree to the tangent vector of this geom only if Tangent/=0.d0 |
121 |
Norm=sqrt(dot_product(Tangent,Tangent)) |
122 |
IF (Norm.GT.eps) THEN |
123 |
ALLOCATE(Tanf(NCoord)) |
124 |
|
125 |
! We normalize Tangent |
126 |
Tangent=Tangent/Norm |
127 |
|
128 |
! We convert Tangent into Vfree only displacements. This is useless for now (2007.Apr.23) |
129 |
! as Vfree=Id matrix but it will be usefull as soon as we introduce constraints. |
130 |
DO I=1,NCoord |
131 |
Tanf(I)=dot_product(reshape(Vfree(:,I),(/NCoord/)),Tangent) |
132 |
END DO |
133 |
Tangent=0.d0 |
134 |
DO I=1,NCoord |
135 |
Tangent=Tangent+Tanf(I)*Vfree(:,I) |
136 |
END DO |
137 |
! first we subtract Tangent from vfree |
138 |
DO I=1,NCoord |
139 |
Norm=dot_product(reshape(vfree(:,I),(/NCoord/)),Tangent) |
140 |
Vfree(:,I)=Vfree(:,I)-Norm*Tangent |
141 |
END DO |
142 |
|
143 |
Idx=0. |
144 |
! Schmidt orthogonalization of the Vfree vectors |
145 |
DO I=1,NCoord |
146 |
! We subtract the first vectors, we do it twice as the Schmidt procedure is not numerically stable. |
147 |
DO Isch=1,2 |
148 |
DO J=1,Idx |
149 |
Norm=dot_product(reshape(Vfree(:,I),(/NCoord/)),reshape(Vfree(:,J),(/NCoord/))) |
150 |
Vfree(:,I)=Vfree(:,I)-Norm*Vfree(:,J) |
151 |
END DO |
152 |
END DO |
153 |
Norm=dot_product(reshape(Vfree(:,I),(/NCoord/)),reshape(Vfree(:,I),(/NCoord/))) |
154 |
IF (Norm.GE.crit) THEN |
155 |
Idx=Idx+1 |
156 |
Vfree(:,Idx)=Vfree(:,I)/sqrt(Norm) |
157 |
END IF |
158 |
END DO |
159 |
|
160 |
Print *, 'Idx=', Idx |
161 |
IF (Idx/= NCoord-1) THEN |
162 |
WRITE(*,*) "Pb in orthogonalizing Vfree to tangent for geom",IGeom |
163 |
WRITE(IoOut,*) "Pb in orthogonalizing Vfree to tangent for geom",IGeom |
164 |
STOP |
165 |
END IF |
166 |
|
167 |
DEALLOCATE(Tanf) |
168 |
NFree=Idx |
169 |
ELSE ! Tangent =0, matches IF (Norm.GT.eps) THEN |
170 |
if (debug) WRITE(*,*) "Tangent=0, using full displacement" |
171 |
NFree=NCoord |
172 |
END IF !IF (Norm.GT.eps) THEN |
173 |
|
174 |
if (debug) WRITE(*,*) 'DBG Step_DIIS_All, IGeom, NFree=', IGeom, NFree |
175 |
|
176 |
! We now calculate the new step |
177 |
! we project the hessian onto the free vectors |
178 |
ALLOCATE(HFree(NFree*NFree),Htmp(NCoord,NFree),Grad_free(NFree),Grad_new_free_inter(NFree)) |
179 |
ALLOCATE(Geom_free(NFree),Step_free(NFree),Geom_new_free_inter(NFree),Geom_new_free(NFree)) |
180 |
DO J=1,NFree |
181 |
DO I=1,NCoord |
182 |
Htmp(I,J)=0.d0 |
183 |
DO K=1,NCoord |
184 |
Htmp(I,J)=Htmp(I,J)+Hess(((I-1)*NCoord)+K)*Vfree(K,J) |
185 |
END DO |
186 |
END DO |
187 |
END DO |
188 |
DO J=1,NFree |
189 |
DO I=1,NFree |
190 |
HFree(I+((J-1)*NFree))=0.d0 |
191 |
DO K=1,NCoord |
192 |
HFree(I+((J-1)*NFree))=HFree(I+((J-1)*NFree))+Vfree(K,I)*Htmp(K,J) |
193 |
END DO |
194 |
END DO |
195 |
END DO |
196 |
|
197 |
DO I=1,NFree |
198 |
Grad_free(I)=dot_product(reshape(Vfree(:,I),(/NCoord/)),Grad) |
199 |
Geom_free(I)=dot_product(reshape(Vfree(:,I),(/NCoord/)),Geom) |
200 |
END DO |
201 |
!Added Ends here.*********************************************** |
202 |
|
203 |
!C SPACE SIMPLY LOADS THE CURRENT VALUES OF Geom AND GRAD INTO |
204 |
!C THE ARRAYS GeomSet AND GradSet |
205 |
!C HEAT is never used, not even in Space_all(...) |
206 |
|
207 |
CALL Space_all(NGeomF,IGeom,MRESET,MSET,Geom,Grad,HEAT,NCoord,GeomSet,GradSet,ESET,FRST) |
208 |
|
209 |
IF (PRINT) WRITE(*,'(/,'' GDIIS after Space '')') |
210 |
|
211 |
DO J=1,MSet(IGeom) |
212 |
DO K=1,NFree |
213 |
GradSet_free(IGeom,((J-1)*NFree)+K)=dot_product(reshape(Vfree(:,K),(/NCoord/)),& |
214 |
GradSet(IGeom,((J-1)*NCoord)+1:((J-1)*NCoord)+NCoord)) |
215 |
GeomSet_free(IGeom,((J-1)*NFree)+K)=dot_product(reshape(Vfree(:,K),(/NCoord/)),& |
216 |
GeomSet(IGeom,((J-1)*NCoord)+1:((J-1)*NCoord)+NCoord)) |
217 |
END DO |
218 |
END DO |
219 |
!C |
220 |
!C INITIALIZE SOME VARIABLES AND CONSTANTS |
221 |
!C |
222 |
NDIIS = MSET(IGeom) |
223 |
MPLUS = MSET(IGeom) + 1 |
224 |
MM = MPLUS * MPLUS |
225 |
!C |
226 |
!C COMPUTE THE APPROXIMATE ERROR VECTORS |
227 |
!C |
228 |
INV=-NFree |
229 |
DO 30 I=1,MSET(IGeom) |
230 |
INV = INV + NFree |
231 |
DO 30 J=1,NFree |
232 |
S = 0.D0 |
233 |
KJ=(J*(J-1))/2 |
234 |
DO 10 K=1,J |
235 |
KJ = KJ+1 |
236 |
10 S = S - HFree(KJ) * GradSet_free(IGeom,INV+K) |
237 |
DO 20 K=J+1,NFree |
238 |
KJ = (K*(K-1))/2+J |
239 |
20 S = S - HFree(KJ) * GradSet_free(IGeom,INV+K) |
240 |
30 ERR(IGeom,INV+J) = S |
241 |
|
242 |
!C |
243 |
!C CONSTRUCT THE GDIIS MATRIX |
244 |
!C |
245 |
DO 40 I=1,MM |
246 |
40 B(I) = 1.D0 |
247 |
|
248 |
JJ=0 |
249 |
INV=-NFree |
250 |
DO 50 I=1,MSET(IGeom) |
251 |
INV=INV+NFree |
252 |
JNV=-NFree |
253 |
DO 50 J=1,MSET(IGeom) |
254 |
JNV=JNV+NFree |
255 |
JJ = JJ + 1 |
256 |
B(JJ)=0.D0 |
257 |
DO 50 K=1,NFree |
258 |
!Print *, 'B(',JJ,')=', B(JJ) + ERR(IGeom,INV+K) * ERR(IGeom,JNV+K) |
259 |
50 B(JJ) = B(JJ) + ERR(IGeom,INV+K) * ERR(IGeom,JNV+K) |
260 |
|
261 |
! The following shifting is required to correct indices of B_ij elements in the GDIIS matrix. |
262 |
! The correction is needed because the last coloumn of the matrix contains all 1 and one zero. |
263 |
DO 60 I=MSET(IGeom)-1,1,-1 |
264 |
DO 60 J=MSET(IGeom),1,-1 |
265 |
60 B(I*MSET(IGeom)+J+I) = B(I*MSET(IGeom)+J) |
266 |
|
267 |
! For the last row and last column of GEDIIS matrix: |
268 |
DO 70 I=1,MPLUS |
269 |
B(MPLUS*I) = 1.D0 |
270 |
70 B(MPLUS*MSET(IGeom)+I) = 1.D0 |
271 |
B(MM) = 0.D0 |
272 |
!C |
273 |
!C ELIMINATE ERROR VECTORS WITH THE LARGEST NORM |
274 |
!C |
275 |
80 CONTINUE |
276 |
DO 90 I=1,MM |
277 |
90 BS(I) = B(I) |
278 |
|
279 |
IF (NDIIS .EQ. MSET(IGeom)) GO TO 140 |
280 |
DO 130 II=1,MSET(IGeom)-NDIIS |
281 |
XMAX = -1.D10 |
282 |
ITERA = 0 |
283 |
DO 110 I=1,MSET(IGeom) |
284 |
XNORM = 0.D0 |
285 |
INV = (I-1) * MPLUS |
286 |
DO 100 J=1,MSET(IGeom) |
287 |
100 XNORM = XNORM + ABS(B(INV + J)) |
288 |
IF (XMAX.LT.XNORM .AND. XNORM.NE.1.0D0) THEN |
289 |
XMAX = XNORM |
290 |
ITERA = I |
291 |
IONE = INV + I |
292 |
ENDIF |
293 |
110 CONTINUE |
294 |
|
295 |
DO 120 I=1,MPLUS |
296 |
INV = (I-1) * MPLUS |
297 |
DO 120 J=1,MPLUS |
298 |
JNV = (J-1) * MPLUS |
299 |
IF (J.EQ.ITERA) B(INV + J) = 0.D0 |
300 |
B(JNV + I) = B(INV + J) |
301 |
!Print *,'B(JNV + I)=',B(JNV + I) |
302 |
120 CONTINUE |
303 |
B(IONE) = 1.0D0 |
304 |
130 CONTINUE |
305 |
140 CONTINUE |
306 |
!C |
307 |
!C OUTPUT THE GDIIS MATRIX |
308 |
!C |
309 |
IF (DEBUG) THEN |
310 |
WRITE(*,'(/5X,'' GDIIS MATRIX'')') |
311 |
ITmp=min(12,MPLUS) |
312 |
DO IJ=1,MPLUS |
313 |
WRITE(*,'(12(F12.4,1X))') B((IJ-1)*MPLUS+1:(IJ-1)*MPLUS+ITmp) |
314 |
END DO |
315 |
ENDIF |
316 |
!C |
317 |
!C SCALE DIIS MATRIX BEFORE INVERSION |
318 |
!C |
319 |
DO 160 I=1,MPLUS |
320 |
II = MPLUS * (I-1) + I |
321 |
!Print *, 'B(',II,')=', B(II) |
322 |
!Print *, 'GSave(',IGeom,',',I,')=', 1.D0 / DSQRT(1.D-20+DABS(B(II))) |
323 |
160 GSAVE(IGeom,I) = 1.D0 / DSQRT(1.D-20+DABS(B(II))) |
324 |
|
325 |
GSAVE(IGeom,MPLUS) = 1.D0 |
326 |
!Print *, 'GSave(',IGeom,',',MPlus,')=1.D0' |
327 |
|
328 |
DO 170 I=1,MPLUS |
329 |
DO 170 J=1,MPLUS |
330 |
IJ = MPLUS * (I-1) + J |
331 |
170 B(IJ) = B(IJ) * GSAVE(IGeom,I) * GSAVE(IGeom,J) |
332 |
!C |
333 |
!C OUTPUT SCALED GDIIS MATRIX |
334 |
!C |
335 |
IF (DEBUG) THEN |
336 |
WRITE(*,'(/5X,'' GDIIS MATRIX (SCALED)'')') |
337 |
ITmp=min(12,MPLUS) |
338 |
DO IJ=1,MPLUS |
339 |
WRITE(*,'(12(F12.4,1X))') B((IJ-1)*MPLUS+1:(IJ-1)*MPLUS+ITmp) |
340 |
END DO |
341 |
ENDIF |
342 |
!C |
343 |
!C INVERT THE GDIIS MATRIX B |
344 |
!C |
345 |
CALL MINV(B,MPLUS,DET) ! matrix inversion. |
346 |
|
347 |
DO 190 I=1,MPLUS |
348 |
DO 190 J=1,MPLUS |
349 |
IJ = MPLUS * (I-1) + J |
350 |
!Print *, 'B(',IJ,')=', B(IJ) |
351 |
!Print *, 'GSAVE(',IGeom,',',I,')=', GSAVE(IGeom,I) |
352 |
!Print *, 'GSAVE(',IGeom,',',J,')=', GSAVE(IGeom,J) |
353 |
!Print *, 'B(',IJ,')=', B(IJ) * GSAVE(I) * GSAVE(J) |
354 |
190 B(IJ) = B(IJ) * GSAVE(IGeom,I) * GSAVE(IGeom,J) |
355 |
!C |
356 |
!C COMPUTE THE INTERMEDIATE INTERPOLATED PARAMETER AND GRADIENT VECTORS |
357 |
!C |
358 |
!Print *, 'MSET(',IGeom,')=', MSET(IGeom), ' MPLUS=', MPLUS |
359 |
DO 200 K=1,NFree |
360 |
Geom_new_free_inter(K) = 0.D0 |
361 |
Grad_new_free_inter(K) = 0.D0 |
362 |
DO 200 I=1,MSET(IGeom) |
363 |
INK = (I-1) * NFree + K |
364 |
Geom_new_free_inter(K) = Geom_new_free_inter(K) + B(MPLUS*MSET(IGeom)+I) * GeomSet_free(IGeom,INK) |
365 |
!Print *, 'Geom_new_free_inter(',K,')=', Geom_new_free_inter(K) |
366 |
!Print *, 'B(MPLUS*MSET(',IGeom,')+',I,')=', B(MPLUS*MSET(IGeom)+I) |
367 |
!Print *, 'GeomSet_free(',IGeom,',',INK,')=', GeomSet_free(IGeom,INK) |
368 |
200 Grad_new_free_inter(K) = Grad_new_free_inter(K) + B(MPLUS*MSET(IGeom)+I) * GradSet_free(IGeom,INK) |
369 |
HP=0.D0 |
370 |
DO 210 I=1,MSET(IGeom) |
371 |
210 HP=HP+B(MPLUS*MSET(IGeom)+I)*ESET(I) |
372 |
DO 220 K=1,NFree |
373 |
220 DXTMP(IGeom,K) = Geom_free(K) - Geom_new_free_inter(K) |
374 |
XNORM = SQRT(DOT_PRODUCT(DXTMP(IGeom,1:NFree),DXTMP(IGeom,1:NFree))) |
375 |
IF (PRINT) THEN |
376 |
WRITE (6,'(/10X,''DEVIATION IN X '',F10.6, 8X,''DETERMINANT '',G9.3)') XNORM,DET |
377 |
WRITE(*,'(10X,''GDIIS COEFFICIENTS'')') |
378 |
WRITE(*,'(10X,5F12.5)') (B(MPLUS*MSET(IGeom)+I),I=1,MSET(IGeom)) |
379 |
ENDIF |
380 |
|
381 |
!C THE FOLLOWING TOLERENCES FOR XNORM AND DET ARE SOMEWHAT ARBITRARY! |
382 |
THRES = MAX(10.D0**(-NFree), 1.D-25) |
383 |
IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN |
384 |
IF (PRINT)THEN |
385 |
WRITE(*,*) "THE DIIS MATRIX IS ILL CONDITIONED" |
386 |
WRITE(*,*) " - PROBABLY, VECTORS ARE LINEARLY DEPENDENT - " |
387 |
WRITE(*,*) "THE DIIS STEP WILL BE REPEATED WITH A SMALLER SPACE" |
388 |
END IF |
389 |
DO 230 K=1,MM |
390 |
230 B(K) = BS(K) |
391 |
NDIIS = NDIIS - 1 |
392 |
IF (NDIIS .GT. 0) GO TO 80 |
393 |
IF (PRINT) WRITE(*,'(10X,''NEWTON-RAPHSON STEP TAKEN'')') |
394 |
DO 240 K=1,NFree |
395 |
Geom_new_free_inter(K) = Geom_free(K) |
396 |
240 Grad_new_free_inter(K) = Grad_free(K) |
397 |
ENDIF ! matches IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN, L378 |
398 |
|
399 |
! q_{m+1} = q'_{m+1} - H^{-1}g'_{m+1} |
400 |
Geom_new_free=0.d0 |
401 |
DO I = 1, NFree |
402 |
DO J = 1, NFree |
403 |
! If Hinv=.False., then we need to invert Hess |
404 |
!Geom_new_free(:) = Geom_new_free(:) + HFree(:,I)*Grad_new_free_inter(I) |
405 |
Geom_new_free(J) = Geom_new_free(J) + HFree(I+((J-1)*NFree))*Grad_new_free_inter(I) |
406 |
END DO |
407 |
END DO |
408 |
Geom_new_free(:) = Geom_new_free_inter(:) - Geom_new_free(:) |
409 |
|
410 |
Step_free = Geom_new_free - Geom_free |
411 |
|
412 |
Step = 0.d0 |
413 |
DO I=1,NFree |
414 |
Step = Step + Step_free(I)*Vfree(:,I) |
415 |
END DO |
416 |
|
417 |
DEALLOCATE(Hfree,Htmp,Grad_free,Grad_new_free_inter,Step_free,Geom_free) |
418 |
DEALLOCATE(Geom_new_free_inter,Geom_new_free) |
419 |
|
420 |
IF (PRINT) WRITE(*,'(/,'' END GDIIS '',/)') |
421 |
|
422 |
END SUBROUTINE Step_diis_all |