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