Statistiques
| Révision :

root / src / Step_GEDIIS.f90

Historique | Voir | Annoter | Télécharger (17,08 ko)

1 1 pfleura2
     ! Geom = input parameter vector (Geometry), Grad = input gradient vector.
2 1 pfleura2
     ! HEAT is Energy(Geom)
3 1 pfleura2
      SUBROUTINE Step_GEDIIS(Geom_new,Geom,Grad,HEAT,Hess,NCoord,FRST)
4 12 pfleura2
! This routine was adapted from the public domain mopac6 diis.f
5 12 pfleura2
!  source file (c) 2009, Stewart Computational Chemistry.
6 12 pfleura2
!  <http://www.openmopac.net/Downloads/Downloads.html>
7 12 pfleura2
!
8 12 pfleura2
!----------------------------------------------------------------------
9 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
10 12 pfleura2
!  Centre National de la Recherche Scientifique,
11 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
12 12 pfleura2
!
13 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
14 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
15 12 pfleura2
!
16 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
17 12 pfleura2
!  Contact: optnpath@gmail.com
18 12 pfleura2
!
19 12 pfleura2
! This file is part of "Opt'n Path".
20 12 pfleura2
!
21 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
22 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
23 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
24 12 pfleura2
!  or (at your option) any later version.
25 12 pfleura2
!
26 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
27 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
28 12 pfleura2
!
29 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
30 12 pfleura2
!  GNU Affero General Public License for more details.
31 12 pfleura2
!
32 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
33 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
34 12 pfleura2
!
35 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
36 12 pfleura2
! for commercial licensing opportunities.
37 12 pfleura2
!----------------------------------------------------------------------
38 1 pfleura2
39 1 pfleura2
    use Io_module
40 1 pfleura2
41 1 pfleura2
      IMPLICIT NONE
42 1 pfleura2
43 1 pfleura2
      INTEGER(KINT) :: NCoord
44 1 pfleura2
      REAL(KREAL) :: Geom_new(NCoord), Grad(NCoord), Hess(NCoord*NCoord)
45 1 pfleura2
    REAL(KREAL), INTENT(IN) :: Geom(NCoord)
46 1 pfleura2
    REAL(KREAL) :: HEAT ! HEAT= Energy
47 1 pfleura2
      LOGICAL :: FRST
48 1 pfleura2
49 1 pfleura2
      ! MRESET = maximum number of iterations.
50 1 pfleura2
      INTEGER(KINT), PARAMETER :: MRESET=15, M2=(MRESET+1)*(MRESET+1) !M2 = 256
51 1 pfleura2
      REAL(KREAL), ALLOCATABLE, SAVE :: GeomSet(:), GradSet(:) ! MRESET*NCoord
52 1 pfleura2
      REAL(KREAL), ALLOCATABLE, SAVE :: DX(:), GSAVE(:) !NCoord
53 1 pfleura2
    REAL(KREAL), SAVE :: ESET(MRESET)
54 1 pfleura2
    REAL(KREAL) :: ESET_tmp(MRESET), B(M2),BS(M2),BST(M2), B_tmp(M2) ! M2=256
55 1 pfleura2
      LOGICAL DEBUG, PRINT, ci_lt_zero
56 1 pfleura2
      INTEGER(KINT), SAVE :: MSET ! mth Iteration
57 1 pfleura2
    REAL(KREAL) :: ci(MRESET), ci_tmp(MRESET) ! MRESET = maximum number of iterations.
58 2 pfleura2
      INTEGER(KINT) :: NGEDIIS, MPLUS, INV, ITERA, MM, cis_zero
59 2 pfleura2
      INTEGER(KINT) :: I, J, K, JJ, JNV, II, IONE, IJ, IX, JX, KX
60 2 pfleura2
    INTEGER(KINT) :: current_size_B_mat, MyPointer
61 2 pfleura2
      REAL(KREAL) :: XMax, XNorm, DET, THRES, tmp, ER_star, ER_star_tmp
62 1 pfleura2
63 1 pfleura2
      DEBUG=.TRUE.
64 1 pfleura2
      PRINT=.FALSE.
65 1 pfleura2
66 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''      BEGIN GEDIIS   '')')
67 1 pfleura2
68 1 pfleura2
      ! Initialization
69 1 pfleura2
      IF (FRST) THEN
70 1 pfleura2
      ! FRST will be set to False in SPACE_GEDIIS, so no need to modify it here
71 1 pfleura2
         IF (ALLOCATED(GeomSet)) THEN
72 1 pfleura2
            IF (PRINT)  WRITE(*,'(/,''    In FRST, GEDIIS Dealloc  '')')
73 1 pfleura2
            DEALLOCATE(GeomSet,GradSet,DX,GSave)
74 1 pfleura2
            RETURN
75 1 pfleura2
         ELSE
76 1 pfleura2
            IF (PRINT)  WRITE(*,'(/,''     In FRST,  GEDIIS Alloc  '')')
77 1 pfleura2
            ALLOCATE(GeomSet(MRESET*NCoord),GradSet(MRESET*NCoord),DX(NCoord),GSAVE(NCoord))
78 1 pfleura2
         END IF
79 1 pfleura2
      END IF ! IF (FRST) THEN
80 1 pfleura2
81 1 pfleura2
      ! SPACE_GEDIIS SIMPLY LOADS THE CURRENT VALUES OF Geom AND Grad INTO THE ARRAYS GeomSet
82 1 pfleura2
      ! AND GradSet, MSET is set to zero and then 1 in SPACE_GEDIIS at first iteration.
83 1 pfleura2
      CALL SPACE_GEDIIS(MRESET,MSET,Geom,Grad,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
84 1 pfleura2
85 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''       GEDIIS after SPACE_GEDIIS  '')')
86 1 pfleura2
87 1 pfleura2
      ! INITIALIZE SOME VARIABLES AND CONSTANTS:
88 1 pfleura2
      NGEDIIS = MSET !MSET=mth iteration
89 1 pfleura2
      MPLUS = MSET + 1
90 1 pfleura2
      MM = MPLUS * MPLUS
91 1 pfleura2
92 1 pfleura2
      ! CONSTRUCT THE GEDIIS MATRIX:
93 1 pfleura2
      ! B_ij calculations from <B_ij=(g_i-g_j)(R_i-R_j)>
94 1 pfleura2
      JJ=0
95 1 pfleura2
      INV=-NCoord
96 1 pfleura2
      DO I=1,MSET
97 1 pfleura2
         INV=INV+NCoord
98 1 pfleura2
         JNV=-NCoord
99 1 pfleura2
         DO J=1,MSET
100 1 pfleura2
            JNV=JNV+NCoord
101 1 pfleura2
            JJ = JJ + 1
102 1 pfleura2
            B(JJ)=0.D0
103 1 pfleura2
      DO K=1, NCoord
104 1 pfleura2
         B(JJ) = B(JJ) + (((GradSet(INV+K)-GradSet(JNV+K))*(GeomSet(INV+K)-GeomSet(JNV+K)))/2.D0)
105 1 pfleura2
      END DO
106 1 pfleura2
         END DO
107 1 pfleura2
      END DO
108 1 pfleura2
109 1 pfleura2
     ! The following shifting is required to correct indices of B_ij elements in the GEDIIS matrix.
110 1 pfleura2
   ! The correction is needed because the last coloumn of the matrix contains all 1 and one zero.
111 1 pfleura2
      DO I=MSET-1,1,-1
112 1 pfleura2
         DO J=MSET,1,-1
113 1 pfleura2
            B(I*MSET+J+I) = B(I*MSET+J)
114 1 pfleura2
         END DO
115 1 pfleura2
    END DO
116 1 pfleura2
117 1 pfleura2
      ! for last row and last column of GEDIIS matrix
118 1 pfleura2
      DO I=1,MPLUS
119 1 pfleura2
         B(MPLUS*I) = 1.D0
120 1 pfleura2
         B(MPLUS*MSET+I) = 1.D0
121 1 pfleura2
      END DO
122 1 pfleura2
      B(MM) = 0.D0
123 1 pfleura2
124 1 pfleura2
    DO I=1, MPLUS
125 1 pfleura2
       !WRITE(*,'(10(1X,F20.4))') B((I-1)*MPLUS+1:I*(MPLUS))
126 1 pfleura2
    END DO
127 1 pfleura2
128 1 pfleura2
      ! ELIMINATE ERROR VECTORS WITH THE LARGEST NORM:
129 1 pfleura2
   80 CONTINUE
130 1 pfleura2
      DO I=1,MM !MM = (MSET+1) * (MSET+1)
131 1 pfleura2
         BS(I) = B(I) !just a copy of the original B (GEDIIS) matrix
132 1 pfleura2
      END DO
133 1 pfleura2
134 1 pfleura2
      IF (NGEDIIS .NE. MSET) THEN
135 1 pfleura2
        DO II=1,MSET-NGEDIIS
136 1 pfleura2
           XMAX = -1.D10
137 1 pfleura2
           ITERA = 0
138 1 pfleura2
           DO I=1,MSET
139 1 pfleura2
              XNORM = 0.D0
140 1 pfleura2
              INV = (I-1) * MPLUS
141 1 pfleura2
              DO J=1,MSET
142 1 pfleura2
                 XNORM = XNORM + ABS(B(INV + J))
143 1 pfleura2
              END DO
144 1 pfleura2
              IF (XMAX.LT.XNORM .AND. XNORM.NE.1.0D0) THEN
145 1 pfleura2
                 XMAX = XNORM
146 1 pfleura2
                 ITERA = I
147 1 pfleura2
                 IONE = INV + I
148 1 pfleura2
              ENDIF
149 1 pfleura2
           END DO
150 1 pfleura2
151 1 pfleura2
           DO I=1,MPLUS
152 1 pfleura2
              INV = (I-1) * MPLUS
153 1 pfleura2
              DO J=1,MPLUS
154 1 pfleura2
                 JNV = (J-1) * MPLUS
155 1 pfleura2
                 IF (J.EQ.ITERA) B(INV + J) = 0.D0
156 1 pfleura2
                 B(JNV + I) = B(INV + J)
157 1 pfleura2
              END DO
158 1 pfleura2
       END DO
159 1 pfleura2
           B(IONE) = 1.0D0
160 1 pfleura2
        END DO
161 1 pfleura2
    END IF ! matches IF (NGEDIIS .NE. MSET) THEN
162 1 pfleura2
163 1 pfleura2
      ! SCALE GEDIIS MATRIX BEFORE INVERSION:
164 1 pfleura2
      DO I=1,MPLUS
165 1 pfleura2
         II = MPLUS * (I-1) + I ! B(II)=diagonal elements of B matrix
166 1 pfleura2
         GSAVE(I) = 1.D0 / DSQRT(1.D-20+DABS(B(II)))
167 1 pfleura2
     !Print *, 'GSAVE(',I,')=', GSAVE(I)
168 1 pfleura2
      END DO
169 1 pfleura2
      GSAVE(MPLUS) = 1.D0
170 1 pfleura2
      DO I=1,MPLUS
171 1 pfleura2
         DO J=1,MPLUS
172 1 pfleura2
            IJ = MPLUS * (I-1) + J
173 1 pfleura2
            B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J)
174 1 pfleura2
         END DO
175 1 pfleura2
      END DO
176 1 pfleura2
177 1 pfleura2
     ! INVERT THE GEDIIS MATRIX B:
178 1 pfleura2
    DO I=1, MPLUS
179 1 pfleura2
       !WRITE(*,'(10(1X,F20.4))') B((I-1)*MPLUS+1:I*(MPLUS))
180 1 pfleura2
    END DO
181 1 pfleura2
182 1 pfleura2
      CALL MINV(B,MPLUS,DET) ! matrix inversion.
183 1 pfleura2
184 1 pfleura2
    DO I=1, MPLUS
185 1 pfleura2
       !WRITE(*,'(10(1X,F20.16))') B((I-1)*MPLUS+1:I*(MPLUS))
186 1 pfleura2
    END DO
187 1 pfleura2
188 1 pfleura2
      DO I=1,MPLUS
189 1 pfleura2
         DO J=1,MPLUS
190 1 pfleura2
            IJ = MPLUS * (I-1) + J
191 1 pfleura2
            B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J)
192 1 pfleura2
         END DO
193 1 pfleura2
      END DO
194 1 pfleura2
195 1 pfleura2
      ! COMPUTE THE NEW INTERPOLATED PARAMETER VECTOR (Geometry):
196 1 pfleura2
    ci=0.d0
197 1 pfleura2
    ci_tmp=0.d0
198 1 pfleura2
199 1 pfleura2
    ci_lt_zero= .FALSE.
200 1 pfleura2
    DO I=1, MSET
201 1 pfleura2
     DO J=1, MSET ! B matrix is read column-wise
202 1 pfleura2
        ci(I)=ci(I)+B((J-1)*(MPLUS)+I)*ESET(J) !ESET is energy set, yet to be fixed.
203 1 pfleura2
     END DO
204 1 pfleura2
     ci(I)=ci(I)+B((MPLUS-1)*(MPLUS)+I)
205 1 pfleura2
     !Print *, 'NO ci < 0 yet, c(',I,')=', ci(I)
206 1 pfleura2
     IF((ci(I) .LT. 0.0D0) .OR. (ci(I) .GT. 1.0D0)) THEN
207 1 pfleura2
       ci_lt_zero=.TRUE.
208 1 pfleura2
       EXIT
209 1 pfleura2
     END IF
210 1 pfleura2
      END DO !matches DO I=1, MSET
211 1 pfleura2
212 1 pfleura2
    IF (ci_lt_zero) Then
213 1 pfleura2
       cis_zero = 0
214 1 pfleura2
         ER_star = 0.D0
215 1 pfleura2
     ER_star_tmp = 1e32
216 1 pfleura2
217 1 pfleura2
     ! B_ij calculations from <B_ij=(g_i-g_j)(R_i-R_j)>, Full B matrix created first and then rows and columns are removed.
218 1 pfleura2
         JJ=0
219 1 pfleura2
         INV=-NCoord
220 1 pfleura2
         DO IX=1,MSET
221 1 pfleura2
            INV=INV+NCoord
222 1 pfleura2
            JNV=-NCoord
223 1 pfleura2
            DO JX=1,MSET
224 1 pfleura2
               JNV=JNV+NCoord
225 1 pfleura2
               JJ = JJ + 1
226 1 pfleura2
               BST(JJ)=0.D0
227 1 pfleura2
           DO KX=1, NCoord
228 1 pfleura2
              BST(JJ) = BST(JJ) + (((GradSet(INV+KX)-GradSet(JNV+KX))*(GeomSet(INV+KX)-GeomSet(JNV+KX)))/2.D0)
229 1 pfleura2
           END DO
230 1 pfleura2
            END DO
231 1 pfleura2
       END DO
232 1 pfleura2
233 1 pfleura2
     DO I=1, (2**MSET)-2 ! all (2**MSET)-2 combinations of cis, except the one where all cis are .GT. 0 and .LT. 1
234 1 pfleura2
         ci(:)=1.D0
235 1 pfleura2
         ! find out which cis are zero in I:
236 1 pfleura2
       DO IX=1, MSET
237 1 pfleura2
          JJ=IAND(I, 2**(IX-1))
238 1 pfleura2
        IF(JJ .EQ. 0) Then
239 1 pfleura2
          ci(IX)=0.D0
240 1 pfleura2
          END IF
241 1 pfleura2
       END DO
242 1 pfleura2
243 1 pfleura2
       ci_lt_zero = .FALSE.
244 1 pfleura2
       ! B_ij calculations from <B_ij=(g_i-g_j)(R_i-R_j)>, Full B matrix created first and then rows and columns are removed.
245 1 pfleura2
       DO IX=1, MSET*MSET
246 1 pfleura2
                B(IX) = BST(IX) !just a copy of the original B (GEDIIS) matrix
247 1 pfleura2
             END DO
248 1 pfleura2
249 1 pfleura2
             ! Removal of KXth row and KXth column in order to accomodate cI to be zero:
250 1 pfleura2
       current_size_B_mat=MSET
251 1 pfleura2
       cis_zero = 0
252 1 pfleura2
       ! The bits of I (index of the upper loop 'DO I=1, (2**MSET)-2'), gives which cis are zero.
253 1 pfleura2
       DO KX=1, MSET ! searching for each bit of I (index of the upper loop 'DO I=1, (2**MSET)-2')
254 1 pfleura2
          IF (ci(KX) .EQ. 0.D0) Then !remove KXth row and KXth column
255 1 pfleura2
           cis_zero = cis_zero + 1
256 1 pfleura2
257 1 pfleura2
             ! First row removal: (B matrix is read column-wise)
258 1 pfleura2
             JJ=0
259 1 pfleura2
                   DO IX=1,current_size_B_mat ! columns reading
260 1 pfleura2
                      DO JX=1,current_size_B_mat ! rows reading
261 1 pfleura2
                 IF (JX .NE. KX) Then
262 1 pfleura2
                     JJ = JJ + 1
263 1 pfleura2
                     B_tmp(JJ) = B((IX-1)*current_size_B_mat+JX)
264 1 pfleura2
                 END IF
265 1 pfleura2
              END DO
266 1 pfleura2
             END DO
267 1 pfleura2
268 1 pfleura2
             DO IX=1,current_size_B_mat*(current_size_B_mat-1)
269 1 pfleura2
                B(IX) = B_tmp(IX)
270 1 pfleura2
             END DO
271 1 pfleura2
272 1 pfleura2
             ! Now column removal:
273 1 pfleura2
             JJ=0
274 1 pfleura2
                   DO IX=1,KX-1 ! columns reading
275 1 pfleura2
                      DO JX=1,current_size_B_mat-1 ! rows reading
276 1 pfleura2
                 JJ = JJ + 1
277 1 pfleura2
                 B_tmp(JJ) = B(JJ)
278 1 pfleura2
              END DO
279 1 pfleura2
             END DO
280 1 pfleura2
281 1 pfleura2
                   DO IX=KX+1,current_size_B_mat
282 1 pfleura2
                      DO JX=1,current_size_B_mat-1
283 1 pfleura2
                 JJ = JJ + 1
284 1 pfleura2
                    B_tmp(JJ) = B(JJ+current_size_B_mat-1)
285 1 pfleura2
              END DO
286 1 pfleura2
             END DO
287 1 pfleura2
288 1 pfleura2
             DO IX=1,(current_size_B_mat-1)*(current_size_B_mat-1)
289 1 pfleura2
                B(IX) = B_tmp(IX)
290 1 pfleura2
             END DO
291 1 pfleura2
           current_size_B_mat = current_size_B_mat - 1
292 1 pfleura2
        END IF ! matches IF (ci(KX) .EQ. 0.D0) Then !remove
293 1 pfleura2
           END DO ! matches DO KX=1, MSET
294 1 pfleura2
295 1 pfleura2
       ! The following shifting is required to correct indices of B_ij elements in the GEDIIS matrix.
296 1 pfleura2
       ! The correction is needed because the last coloumn and row of the matrix contains all 1 and one zero.
297 1 pfleura2
       DO IX=MSET-cis_zero-1,1,-1
298 1 pfleura2
        DO JX=MSET-cis_zero,1,-1
299 1 pfleura2
           B(IX*(MSET-cis_zero)+JX+IX) = B(IX*(MSET-cis_zero)+JX)
300 1 pfleura2
        END DO
301 1 pfleura2
       END DO
302 1 pfleura2
303 1 pfleura2
       ! for last row and last column of GEDIIS matrix
304 1 pfleura2
       DO IX=1,MPLUS-cis_zero
305 1 pfleura2
        B((MPLUS-cis_zero)*IX) = 1.D0
306 1 pfleura2
        B((MPLUS-cis_zero)*(MSET-cis_zero)+IX) = 1.D0
307 1 pfleura2
       END DO
308 1 pfleura2
       B((MPLUS-cis_zero) * (MPLUS-cis_zero)) = 0.D0
309 1 pfleura2
310 1 pfleura2
           DO IX=1, MPLUS
311 1 pfleura2
              !WRITE(*,'(10(1X,F20.4))') B((IX-1)*MPLUS+1:IX*(MPLUS))
312 1 pfleura2
           END DO
313 1 pfleura2
314 1 pfleura2
       ! ELIMINATE ERROR VECTORS WITH THE LARGEST NORM:
315 1 pfleura2
             IF (NGEDIIS .NE. MSET) THEN
316 1 pfleura2
          JX = min(MSET-NGEDIIS,MSET-cis_zero-1)
317 1 pfleura2
                DO II=1,JX
318 1 pfleura2
                   XMAX = -1.D10
319 1 pfleura2
                   ITERA = 0
320 1 pfleura2
                   DO IX=1,MSET-cis_zero
321 1 pfleura2
                      XNORM = 0.D0
322 1 pfleura2
                      INV = (IX-1) * (MPLUS-cis_zero)
323 1 pfleura2
                      DO J=1,MSET-cis_zero
324 1 pfleura2
                         XNORM = XNORM + ABS(B(INV + J))
325 1 pfleura2
                      END DO
326 1 pfleura2
                      IF (XMAX.LT.XNORM .AND. XNORM.NE.1.0D0) THEN
327 1 pfleura2
                         XMAX = XNORM
328 1 pfleura2
                         ITERA = IX
329 1 pfleura2
                         IONE = INV + IX
330 1 pfleura2
                      ENDIF
331 1 pfleura2
           END DO
332 1 pfleura2
333 1 pfleura2
                   DO IX=1,MPLUS-cis_zero
334 1 pfleura2
                      INV = (IX-1) * (MPLUS-cis_zero)
335 1 pfleura2
                      DO J=1,MPLUS-cis_zero
336 1 pfleura2
                         JNV = (J-1) * (MPLUS-cis_zero)
337 1 pfleura2
                         IF (J.EQ.ITERA) B(INV + J) = 0.D0
338 1 pfleura2
                         B(JNV + IX) = B(INV + J)
339 1 pfleura2
            END DO
340 1 pfleura2
               END DO
341 1 pfleura2
                   B(IONE) = 1.0D0
342 1 pfleura2
          END DO
343 1 pfleura2
           END IF ! matches IF (NGEDIIS .NE. MSET) THEN
344 1 pfleura2
345 1 pfleura2
       ! SCALE GEDIIS MATRIX BEFORE INVERSION:
346 1 pfleura2
       DO IX=1,MPLUS-cis_zero
347 1 pfleura2
        II = (MPLUS-cis_zero) * (IX-1) + IX ! B(II)=diagonal elements of B matrix
348 1 pfleura2
        GSAVE(IX) = 1.D0 / DSQRT(1.D-20+DABS(B(II)))
349 1 pfleura2
       END DO
350 1 pfleura2
       GSAVE(MPLUS-cis_zero) = 1.D0
351 1 pfleura2
       DO IX=1,MPLUS-cis_zero
352 1 pfleura2
        DO JX=1,MPLUS-cis_zero
353 1 pfleura2
           IJ = (MPLUS-cis_zero) * (IX-1) + JX
354 1 pfleura2
           B(IJ) = B(IJ) * GSAVE(IX) * GSAVE(JX)
355 1 pfleura2
        END DO
356 1 pfleura2
       END DO
357 1 pfleura2
358 1 pfleura2
       ! INVERT THE GEDIIS MATRIX B:
359 1 pfleura2
       CALL MINV(B,MPLUS-cis_zero,DET) ! matrix inversion.
360 1 pfleura2
361 1 pfleura2
       DO IX=1,MPLUS-cis_zero
362 1 pfleura2
        DO JX=1,MPLUS-cis_zero
363 1 pfleura2
           IJ = (MPLUS-cis_zero) * (IX-1) + JX
364 1 pfleura2
           B(IJ) = B(IJ) * GSAVE(IX) * GSAVE(JX)
365 1 pfleura2
        END DO
366 1 pfleura2
       END DO
367 1 pfleura2
368 1 pfleura2
           DO IX=1, MPLUS
369 1 pfleura2
              !WRITE(*,'(10(1X,F20.4))') B((IX-1)*MPLUS+1:IX*(MPLUS))
370 1 pfleura2
           END DO
371 1 pfleura2
372 1 pfleura2
             ! ESET is rearranged to handle zero cis and stored in ESET_tmp:
373 1 pfleura2
       JJ=0
374 1 pfleura2
       DO IX=1, MSET
375 1 pfleura2
        IF (ci(IX) .NE. 0) Then
376 1 pfleura2
           JJ=JJ+1
377 1 pfleura2
           ESET_tmp(JJ) = ESET(IX)
378 1 pfleura2
        END IF
379 1 pfleura2
       END DO
380 1 pfleura2
381 1 pfleura2
       ! DETERMINATION OF nonzero cis:
382 1 pfleura2
       MyPointer=1
383 1 pfleura2
            DO IX=1, MSET-cis_zero
384 1 pfleura2
          tmp = 0.D0
385 1 pfleura2
            DO J=1, MSET-cis_zero ! B matrix is read column-wise
386 1 pfleura2
           tmp=tmp+B((J-1)*(MPLUS-cis_zero)+IX)*ESET_tmp(J)
387 1 pfleura2
        END DO
388 1 pfleura2
            tmp=tmp+B((MPLUS-cis_zero-1)*(MPLUS-cis_zero)+IX)
389 1 pfleura2
            IF((tmp .LT. 0.0D0) .OR. (tmp .GT. 1.0D0)) THEN
390 1 pfleura2
               ci_lt_zero=.TRUE.
391 1 pfleura2
               EXIT
392 1 pfleura2
        ELSE
393 1 pfleura2
           DO JX=MyPointer,MSET
394 1 pfleura2
              IF (ci(JX) .NE. 0) Then
395 1 pfleura2
                 ci(JX) = tmp
396 1 pfleura2
               MyPointer=JX+1
397 1 pfleura2
               EXIT
398 1 pfleura2
            END IF
399 1 pfleura2
           END DO
400 1 pfleura2
            END IF
401 1 pfleura2
             END DO !matches DO I=1, MSET-cis_zero
402 1 pfleura2
           !Print *, 'Local set of cis, first 10:, MSET=', MSET, ', I of (2**MSET)-2=', I
403 1 pfleura2
       !WRITE(*,'(10(1X,F20.4))') ci(1:MSET)
404 1 pfleura2
           !Print *, 'Local set of cis ends:****************************************'
405 1 pfleura2
406 1 pfleura2
             ! new set of cis determined based on the lower energy (ER_star):
407 1 pfleura2
       IF (.NOT. ci_lt_zero) Then
408 1 pfleura2
                Call Energy_GEDIIS(MRESET,MSET,ci,GeomSet,GradSet,ESET,NCoord,ER_star)
409 1 pfleura2
        IF (ER_star .LT. ER_star_tmp) Then
410 1 pfleura2
           ci_tmp=ci
411 1 pfleura2
           ER_star_tmp = ER_star
412 1 pfleura2
        END IF
413 1 pfleura2
             END IF ! matches IF (.NOT. ci_lt_zero) Then
414 1 pfleura2
          END DO !matches DO I=1, (2**K)-2 ! all (2**K)-2 combinations of cis, except the one where all cis are .GT. 0 and .LT. 1
415 1 pfleura2
      ci = ci_tmp
416 1 pfleura2
    END IF! matches IF (ci_lt_zero) Then
417 1 pfleura2
418 1 pfleura2
    Print *, 'Final set of cis, first 10:***********************************'
419 1 pfleura2
    WRITE(*,'(10(1X,F20.4))') ci(1:MSET)
420 1 pfleura2
    Print *, 'Final set of cis ends:****************************************'
421 1 pfleura2
    Geom_new(:) = 0.D0
422 1 pfleura2
    DO I=1, MSET
423 1 pfleura2
         Geom_new(:) = Geom_new(:) + (ci(I)*GeomSet((I-1)*NCoord+1:I*NCoord)) !MPLUS=MSET+1
424 1 pfleura2
     ! R_(N+1)=R*+DeltaR:
425 1 pfleura2
     DO J=1, NCoord
426 1 pfleura2
      tmp=0.D0
427 1 pfleura2
      DO K=1,NCoord
428 1 pfleura2
         !tmp=tmp+Hess((J-1)*NCoord+K)*GradSet((I-1)*NCoord+K) ! If Hinv=.False., then we need to invert Hess
429 1 pfleura2
      END DO
430 1 pfleura2
      Geom_new(J) = Geom_new(J) - (ci(I)*tmp)
431 1 pfleura2
     END DO
432 1 pfleura2
    END DO
433 1 pfleura2
434 1 pfleura2
    DX(:) = Geom(:) - Geom_new(:)
435 1 pfleura2
436 1 pfleura2
      XNORM = SQRT(DOT_PRODUCT(DX,DX))
437 1 pfleura2
      IF (PRINT) THEN
438 1 pfleura2
         WRITE (6,'(/10X,''DEVIATION IN X '',F10.4,8X,''DETERMINANT '',G9.3)') XNORM, DET
439 1 pfleura2
         !WRITE(*,'(10X,''GEDIIS COEFFICIENTS'')')
440 1 pfleura2
         !WRITE(*,'(10X,5F12.5)') (B(MPLUS*MSET+I),I=1,MSET)
441 1 pfleura2
      ENDIF
442 1 pfleura2
443 1 pfleura2
      ! THE FOLLOWING TOLERENCES FOR XNORM AND DET ARE SOMEWHAT ARBITRARY!
444 1 pfleura2
      THRES = MAX(10.D0**(-NCoord), 1.D-25)
445 1 pfleura2
      IF (XNORM.GT.2.D0 .OR. DABS(DET) .LT. THRES) THEN
446 1 pfleura2
         IF (PRINT)THEN
447 1 pfleura2
            WRITE(*,*) "THE GEDIIS MATRIX IS ILL CONDITIONED"
448 1 pfleura2
            WRITE(*,*) " - PROBABLY, VECTORS ARE LINEARLY DEPENDENT - "
449 1 pfleura2
            WRITE(*,*) "THE GEDIIS STEP WILL BE REPEATED WITH A SMALLER SPACE"
450 1 pfleura2
         END IF
451 1 pfleura2
         DO K=1,MM
452 1 pfleura2
      B(K) = BS(K) ! why this is reverted? Because "IF (NGEDIIS .GT. 0) GO TO 80", see below
453 1 pfleura2
         END DO
454 1 pfleura2
         NGEDIIS = NGEDIIS - 1
455 1 pfleura2
         IF (NGEDIIS .GT. 0) GO TO 80
456 1 pfleura2
         IF (PRINT) WRITE(*,'(10X,''NEWTON-RAPHSON STEP TAKEN'')')
457 1 pfleura2
         Geom_new(:) = Geom(:) ! Geom_new is set to original Geom, thus DX = Geom(:) - Geom_new(:)=zero
458 1 pfleura2
      END IF ! matches IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN
459 1 pfleura2
460 1 pfleura2
   !*******************************************************************************************************************
461 1 pfleura2
    Geom_new(:) = 0.D0
462 1 pfleura2
    DO I=1, MSET
463 1 pfleura2
         Geom_new(:) = Geom_new(:) + (ci(I)*GeomSet((I-1)*NCoord+1:I*NCoord)) !MPLUS=MSET+1
464 1 pfleura2
     ! R_(N+1)=R*+DeltaR:
465 1 pfleura2
     DO J=1, NCoord
466 1 pfleura2
      tmp=0.D0
467 1 pfleura2
      DO K=1,NCoord
468 1 pfleura2
         tmp=tmp+Hess((J-1)*NCoord+K)*GradSet((I-1)*NCoord+K) ! If Hinv=.False., then we need to invert Hess
469 1 pfleura2
      END DO
470 1 pfleura2
      Geom_new(J) = Geom_new(J) - (ci(I)*tmp)
471 1 pfleura2
     END DO
472 1 pfleura2
    END DO
473 1 pfleura2
   !*******************************************************************************************************************
474 1 pfleura2
475 1 pfleura2
      IF (PRINT)  WRITE(*,'(/,''       END GEDIIS  '',/)')
476 1 pfleura2
477 1 pfleura2
      END SUBROUTINE Step_GEDIIS