Statistiques
| Révision :

root / src / Step_GDIIS_Simple_Err.f90

Historique | Voir | Annoter | Télécharger (11,41 ko)

1 1 pfleura2
!C  HEAT is never used, not even in call of Space(...)
2 1 pfleura2
!C  Geom = input parameter vector (Geometry).
3 1 pfleura2
!C  Grad = input gradient vector.
4 2 pfleura2
      SUBROUTINE Step_GDIIS_Simple_Err(NewGeom,Geom,NewGrad,GRAD,HP,HEAT,NCoord,FRST)
5 2 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) :: NCoord
49 2 pfleura2
      REAL(KREAL) :: NewGeom(NCoord), Geom(NCoord), NewGrad(NCoord), GRAD(NCoord)
50 1 pfleura2
      REAL(KREAL) :: HEAT, HP
51 1 pfleura2
      LOGICAL :: FRST
52 1 pfleura2
53 1 pfleura2
!************************************************************************
54 1 pfleura2
!*                                                                      *
55 1 pfleura2
!*     DIIS PERFORMS DIRECT INVERSION IN THE ITERATIVE SUBSPACE         *
56 1 pfleura2
!*                                                                      *
57 1 pfleura2
!*     THIS INVOLVES SOLVING FOR C IN Geom(NEW) = Geom' - HG'           *
58 1 pfleura2
!*                                                                      *
59 1 pfleura2
!*  WHERE Geom' = SUM(C(I)Geom(I), THE C COEFFICIENTES COMING FROM      *
60 1 pfleura2
!*                                                                      *
61 1 pfleura2
!*                   | B   1 | . | C | = | 0 |                          *
62 1 pfleura2
!*                   | 1   0 |   |-L |   | 1 |                          *
63 1 pfleura2
!*                                                                      *
64 1 pfleura2
!* WHERE B(I,J) =GRAD(I)H(T)HGRAD(J)  GRAD(I) = GRADIENT ON CYCLE I     *
65 1 pfleura2
!*                              Hess    = INVERSE HESSIAN               *
66 1 pfleura2
!*                                                                      *
67 1 pfleura2
!*                          REFERENCE                                   *
68 1 pfleura2
!*                                                                      *
69 1 pfleura2
!*  P. CSASZAR, P. PULAY, J. MOL. STRUCT. (THEOCHEM), 114, 31 (1984)    *
70 1 pfleura2
!*                                                                      *
71 1 pfleura2
!************************************************************************
72 1 pfleura2
!************************************************************************
73 1 pfleura2
!*                                                                      *
74 1 pfleura2
!*     GEOMETRY OPTIMIZATION USING THE METHOD OF DIRECT INVERSION IN    *
75 1 pfleura2
!*     THE ITERATIVE SUBSPACE (GDIIS), COMBINED WITH THE BFGS OPTIMIZER *
76 1 pfleura2
!*     (A VARIABLE METRIC METHOD)                                       *
77 1 pfleura2
!*                                                                      *
78 1 pfleura2
!*     WRITTEN BY PETER L. CUMMINS, UNIVERSITY OF SYDNEY, AUSTRALIA     *
79 1 pfleura2
!*                                                                      *
80 1 pfleura2
!*                              REFERENCE                               *
81 1 pfleura2
!*                                                                      *
82 1 pfleura2
!*      "COMPUTATIONAL STRATEGIES FOR THE OPTIMIZATION OF EQUILIBRIUM   *
83 1 pfleura2
!*     GEOMETRIES AND TRANSITION-STATE STRUCTURES AT THE SEMIEMPIRICAL  *
84 1 pfleura2
!*     LEVEL", PETER L. CUMMINS, JILL E. GREADY, J. COMP. CHEM., 10,    *
85 1 pfleura2
!*     939-950 (1989).                                                  *
86 1 pfleura2
!*                                                                      *
87 1 pfleura2
!*     MODIFIED BY JJPS TO CONFORM TO EXISTING MOPAC CONVENTIONS        *
88 1 pfleura2
!*                                                                      *
89 1 pfleura2
!************************************************************************
90 1 pfleura2
91 1 pfleura2
      ! MRESET = number of iterations.
92 1 pfleura2
      INTEGER(KINT), PARAMETER :: MRESET=15, M2=(MRESET+1)*(MRESET+1) !M2 = 256
93 1 pfleura2
      REAL(KREAL), ALLOCATABLE, SAVE :: GeomSet(:), GradSet(:), ERR(:) ! MRESET*NCoord
94 1 pfleura2
      REAL(KREAL) :: ESET(MRESET)
95 1 pfleura2
      REAL(KREAL), ALLOCATABLE, SAVE :: DX(:), GSAVE(:) !NCoord
96 2 pfleura2
      REAL(KREAL) :: B(M2), BS(M2)
97 1 pfleura2
      LOGICAL DEBUG, PRINT
98 1 pfleura2
      INTEGER(KINT), SAVE :: MSET
99 1 pfleura2
      INTEGER(KINT) :: NDIIS, MPLUS, INV, ITERA, MM, I, J, K
100 2 pfleura2
      INTEGER(KINT) :: JJ, JNV, II, IONE, IJ, INK, ITmp
101 2 pfleura2
      REAL(KREAL) :: XMax, XNorm, DET, THRES
102 1 pfleura2
103 1 pfleura2
      DEBUG=.TRUE.
104 1 pfleura2
      PRINT=.TRUE.
105 1 pfleura2
106 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''      BEGIN Step_GDIIS_Simple_Err   '')')
107 1 pfleura2
108 1 pfleura2
      ! Initialization
109 1 pfleura2
      IF (FRST) THEN
110 1 pfleura2
       ! FRST will be set to False in Space, so no need to modify it here
111 1 pfleura2
         IF (ALLOCATED(GeomSet)) THEN
112 1 pfleura2
            IF (PRINT)  WRITE(*,'(/,''    In FRST, Step_GDIIS_Simple_Err Dealloc  '')')
113 1 pfleura2
            DEALLOCATE(GeomSet,GradSet,ERR,DX,GSave)
114 1 pfleura2
            RETURN
115 1 pfleura2
         ELSE
116 1 pfleura2
            IF (PRINT)  WRITE(*,'(/,''     In FRST,  Step_GDIIS_Simple_Err alloc  '')')
117 1 pfleura2
            ALLOCATE(GeomSet(MRESET*NCoord), GradSet(MRESET*NCoord), ERR(MRESET*NCoord))
118 1 pfleura2
            ALLOCATE(DX(NCoord),GSAVE(NCoord))
119 1 pfleura2
         END IF
120 1 pfleura2
      END IF
121 1 pfleura2
122 1 pfleura2
      ! SPACE SIMPLY LOADS THE CURRENT VALUES OF Geom AND GRAD INTO THE ARRAYS GeomSet AND GradSet
123 1 pfleura2
      ! HEAT is never used, not even in Space(...)
124 1 pfleura2
      CALL SPACE(MRESET,MSET,Geom,Grad,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
125 1 pfleura2
126 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''       Step_GDIIS_Simple_Err after Space  '')')
127 1 pfleura2
128 1 pfleura2
      ! INITIALIZE SOME VARIABLES AND CONSTANTS:
129 1 pfleura2
      NDIIS = MSET
130 1 pfleura2
      MPLUS = MSET + 1
131 1 pfleura2
      MM = MPLUS * MPLUS
132 1 pfleura2
133 1 pfleura2
      ! CONSTRUCT THE GDIIS MATRIX:
134 1 pfleura2
      ! B_ij calculations from <B_ij=(g_i-g_j)(R_i-R_j)>
135 1 pfleura2
      JJ=0
136 1 pfleura2
      INV=-NCoord
137 1 pfleura2
      DO I=1,MSET
138 1 pfleura2
         INV=INV+NCoord
139 1 pfleura2
         JNV=-NCoord
140 1 pfleura2
         DO J=1,MSET
141 1 pfleura2
            JNV=JNV+NCoord
142 1 pfleura2
            JJ = JJ + 1
143 1 pfleura2
            B(JJ)=0.D0
144 1 pfleura2
      DO K=1, NCoord
145 1 pfleura2
         B(JJ) = B(JJ) + (((GradSet(INV+K)-GradSet(JNV+K))*(GeomSet(INV+K)-GeomSet(JNV+K)))/2.D0)
146 1 pfleura2
      END DO
147 1 pfleura2
         END DO
148 1 pfleura2
      END DO
149 1 pfleura2
150 1 pfleura2
     ! The following shifting is required to correct indices of B_ij elements in the GDIIS matrix.
151 1 pfleura2
   ! The correction is needed because the last coloumn of the matrix contains all 1 and one zero.
152 1 pfleura2
      DO 60 I=MSET-1,1,-1
153 1 pfleura2
         DO 60 J=MSET,1,-1
154 1 pfleura2
   60 B(I*MSET+J+I) = B(I*MSET+J)
155 1 pfleura2
156 1 pfleura2
      ! for last row and last column of GDIIS matrix
157 1 pfleura2
      DO 70 I=1,MPLUS
158 1 pfleura2
         B(MPLUS*I) = 1.D0
159 1 pfleura2
   70 B(MPLUS*MSET+I) = 1.D0
160 1 pfleura2
      B(MM) = 0.D0
161 1 pfleura2
162 1 pfleura2
      ! ELIMINATE ERROR VECTORS WITH THE LARGEST NORM:
163 1 pfleura2
   80 CONTINUE
164 1 pfleura2
      DO 90 I=1,MM
165 1 pfleura2
   90 BS(I) = B(I)
166 1 pfleura2
      IF (NDIIS .EQ. MSET) GO TO 140
167 1 pfleura2
      DO 130 II=1,MSET-NDIIS
168 1 pfleura2
         XMAX = -1.D10
169 1 pfleura2
         ITERA = 0
170 1 pfleura2
         DO 110 I=1,MSET
171 1 pfleura2
            XNORM = 0.D0
172 1 pfleura2
            INV = (I-1) * MPLUS
173 1 pfleura2
            DO 100 J=1,MSET
174 1 pfleura2
  100       XNORM = XNORM + ABS(B(INV + J))
175 1 pfleura2
            IF (XMAX.LT.XNORM .AND. XNORM.NE.1.0D0) THEN
176 1 pfleura2
               XMAX = XNORM
177 1 pfleura2
               ITERA = I
178 1 pfleura2
               IONE = INV + I
179 1 pfleura2
            ENDIF
180 1 pfleura2
  110    CONTINUE
181 1 pfleura2
         DO 120 I=1,MPLUS
182 1 pfleura2
            INV = (I-1) * MPLUS
183 1 pfleura2
            DO 120 J=1,MPLUS
184 1 pfleura2
               JNV = (J-1) * MPLUS
185 1 pfleura2
               IF (J.EQ.ITERA) B(INV + J) = 0.D0
186 1 pfleura2
               B(JNV + I) = B(INV + J)
187 1 pfleura2
  120    CONTINUE
188 1 pfleura2
         B(IONE) = 1.0D0
189 1 pfleura2
  130 CONTINUE
190 1 pfleura2
  140 CONTINUE
191 1 pfleura2
192 1 pfleura2
      IF (DEBUG) THEN
193 1 pfleura2
194 1 pfleura2
      ! OUTPUT THE GDIIS MATRIX:
195 1 pfleura2
         WRITE(*,'(/5X,'' Step_GDIIS_Simple_Err MATRIX'')')
196 1 pfleura2
         ITmp=min(12,MPLUS)
197 1 pfleura2
         DO IJ=1,MPLUS
198 1 pfleura2
            WRITE(*,'(12(F10.4,1X))') B((IJ-1)*MPLUS+1:(IJ-1)*MPLUS+ITmp)
199 1 pfleura2
         END DO
200 1 pfleura2
      ENDIF
201 1 pfleura2
202 1 pfleura2
      ! SCALE DIIS MATRIX BEFORE INVERSION:
203 1 pfleura2
      DO 160 I=1,MPLUS
204 1 pfleura2
         II = MPLUS * (I-1) + I
205 1 pfleura2
  160 GSAVE(I) = 1.D0 / DSQRT(1.D-20+DABS(B(II)))
206 1 pfleura2
      GSAVE(MPLUS) = 1.D0
207 1 pfleura2
      DO 170 I=1,MPLUS
208 1 pfleura2
         DO 170 J=1,MPLUS
209 1 pfleura2
            IJ = MPLUS * (I-1) + J
210 1 pfleura2
  170 B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J)
211 1 pfleura2
212 1 pfleura2
      IF (DEBUG) THEN
213 1 pfleura2
214 1 pfleura2
      ! OUTPUT SCALED GDIIS MATRIX:
215 1 pfleura2
         WRITE(*,'(/5X,'' Step_GDIIS_Simple_Err MATRIX (SCALED)'')')
216 1 pfleura2
         ITmp=min(12,MPLUS)
217 1 pfleura2
         DO IJ=1,MPLUS
218 1 pfleura2
            WRITE(*,'(12(F10.4,1X))') B((IJ-1)*MPLUS+1:(IJ-1)*MPLUS+ITmp)
219 1 pfleura2
         END DO
220 1 pfleura2
221 1 pfleura2
      ENDIF ! matches IF (DEBUG) THEN
222 1 pfleura2
223 1 pfleura2
      ! INVERT THE GDIIS MATRIX B:
224 1 pfleura2
      CALL MINV(B,MPLUS,DET) ! matrix inversion.
225 1 pfleura2
226 1 pfleura2
      DO 190 I=1,MPLUS
227 1 pfleura2
         DO 190 J=1,MPLUS
228 1 pfleura2
            IJ = MPLUS * (I-1) + J
229 1 pfleura2
  190 B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J)
230 1 pfleura2
231 1 pfleura2
      ! COMPUTE THE INTERMEDIATE INTERPOLATED PARAMETER AND GRADIENT VECTORS:
232 1 pfleura2
      DO 200 K=1,NCoord
233 1 pfleura2
         NewGeom(K) = 0.D0
234 1 pfleura2
         NewGrad(K) = 0.D0
235 1 pfleura2
         DO 200 I=1,MSET
236 1 pfleura2
            INK = (I-1) * NCoord + K
237 1 pfleura2
      !Print *, 'B(',MPLUS*MSET+I,')=', B(MPLUS*MSET+I)
238 1 pfleura2
            NewGeom(K) = NewGeom(K) + B(MPLUS*MSET+I) * GeomSet(INK)
239 1 pfleura2
  200 NewGrad(K) = NewGrad(K) + B(MPLUS*MSET+I) * GradSet(INK)
240 1 pfleura2
      HP=0.D0
241 1 pfleura2
      DO 210 I=1,MSET
242 1 pfleura2
  210 HP=HP+B(MPLUS*MSET+I)*ESET(I)
243 1 pfleura2
244 1 pfleura2
      DO 220 K=1,NCoord
245 1 pfleura2
  220 DX(K) = Geom(K) - NewGeom(K)
246 1 pfleura2
      XNORM = SQRT(DOT_PRODUCT(DX,DX))
247 1 pfleura2
      IF (PRINT) THEN
248 1 pfleura2
         WRITE (6,'(/10X,''DEVIATION IN X '',F7.4,8X,''DETERMINANT '',G9.3)') XNORM,DET
249 1 pfleura2
         WRITE(*,'(10X,''Step_GDIIS_Simple_Err COEFFICIENTS'')')
250 1 pfleura2
         WRITE(*,'(10X,5F12.5)') (B(MPLUS*MSET+I),I=1,MSET)
251 1 pfleura2
      ENDIF
252 1 pfleura2
253 1 pfleura2
      ! THE FOLLOWING TOLERENCES FOR XNORM AND DET ARE SOMEWHAT ARBITRARY:
254 1 pfleura2
      THRES = MAX(10.D0**(-NCoord), 1.D-25)
255 1 pfleura2
      IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN
256 1 pfleura2
         IF (PRINT)THEN
257 1 pfleura2
            WRITE(*,*) "THE DIIS MATRIX IS ILL CONDITIONED"
258 1 pfleura2
            WRITE(*,*) " - PROBABLY, VECTORS ARE LINEARLY DEPENDENT - "
259 1 pfleura2
            WRITE(*,*) "THE DIIS STEP WILL BE REPEATED WITH A SMALLER SPACE"
260 1 pfleura2
         END IF
261 1 pfleura2
         DO 230 K=1,MM
262 1 pfleura2
  230    B(K) = BS(K)
263 1 pfleura2
         NDIIS = NDIIS - 1
264 1 pfleura2
         IF (NDIIS .GT. 0) GO TO 80
265 1 pfleura2
         IF (PRINT) WRITE(*,'(10X,''NEWTON-RAPHSON STEP TAKEN'')')
266 1 pfleura2
         DO 240 K=1,NCoord
267 1 pfleura2
            NewGeom(K) = Geom(K)
268 1 pfleura2
  240       NewGrad(K) = GRAD(K)
269 1 pfleura2
      ENDIF ! matches IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN
270 1 pfleura2
271 1 pfleura2
      !    q_{m+1} = q'_{m+1} - H^{-1}g'_{m+1}
272 1 pfleura2
     ! Hess is a symmetric matrix.
273 1 pfleura2
     !Hess_inv = 1.d0 ! to be deleted.
274 1 pfleura2
     !Call GenInv(NCoord,Reshape(Hess,(/NCoord,NCoord/)),Hess_inv,NCoord) ! Implemented in Mat_util.f90
275 1 pfleura2
     ! H^{-1}g'_{m+1}
276 1 pfleura2
     !Print *, 'Hess_inv='
277 1 pfleura2
    ! Print *, Hess_inv
278 1 pfleura2
     !Geom=0.d0
279 1 pfleura2
     !DO I=1, NCoord
280 1 pfleura2
      !  Geom(:) = Geom(:) + Hess_inv(:,I)*NewGrad(I)
281 1 pfleura2
     !END DO
282 1 pfleura2
     !Geom(:) = NewGeom(:) - Geom(:) ! now Geom is a new geometry.
283 1 pfleura2
284 1 pfleura2
     ! STEP is the difference between the new and old geometry and thus "step":
285 1 pfleura2
         !STEP = Geom - Geom_old
286 1 pfleura2
287 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''       END Step_GDIIS_Simple_Err  '',/)')
288 1 pfleura2
289 1 pfleura2
      END SUBROUTINE Step_GDIIS_Simple_Err