Statistiques
| Révision :

root / src / Step_GEDIIS.f90

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

1
     ! Geom = input parameter vector (Geometry), Grad = input gradient vector.
2
     ! HEAT is Energy(Geom)
3
      SUBROUTINE Step_GEDIIS(Geom_new,Geom,Grad,HEAT,Hess,NCoord,FRST)
4
! This routine was adapted from the public domain mopac6 diis.f 
5
!  source file (c) 2009, Stewart Computational Chemistry.
6
!  <http://www.openmopac.net/Downloads/Downloads.html>
7
!
8
!----------------------------------------------------------------------
9
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
10
!  Centre National de la Recherche Scientifique,
11
!  Université Claude Bernard Lyon 1. All rights reserved.
12
!
13
!  This work is registered with the Agency for the Protection of Programs 
14
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
15
!
16
!  Authors: P. Fleurat-Lessard, P. Dayal
17
!  Contact: optnpath@gmail.com
18
!
19
! This file is part of "Opt'n Path".
20
!
21
!  "Opt'n Path" is free software: you can redistribute it and/or modify
22
!  it under the terms of the GNU Affero General Public License as
23
!  published by the Free Software Foundation, either version 3 of the License,
24
!  or (at your option) any later version.
25
!
26
!  "Opt'n Path" is distributed in the hope that it will be useful,
27
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
28
!
29
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
30
!  GNU Affero General Public License for more details.
31
!
32
!  You should have received a copy of the GNU Affero General Public License
33
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
34
!
35
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
36
! for commercial licensing opportunities.
37
!----------------------------------------------------------------------
38

    
39
    use Io_module
40
    
41
      IMPLICIT NONE
42

    
43
      INTEGER(KINT) :: NCoord
44
      REAL(KREAL) :: Geom_new(NCoord), Grad(NCoord), Hess(NCoord*NCoord)
45
    REAL(KREAL), INTENT(IN) :: Geom(NCoord)
46
    REAL(KREAL) :: HEAT ! HEAT= Energy
47
      LOGICAL :: FRST
48

    
49
      ! MRESET = maximum number of iterations.
50
      INTEGER(KINT), PARAMETER :: MRESET=15, M2=(MRESET+1)*(MRESET+1) !M2 = 256
51
      REAL(KREAL), ALLOCATABLE, SAVE :: GeomSet(:), GradSet(:) ! MRESET*NCoord
52
      REAL(KREAL), ALLOCATABLE, SAVE :: DX(:), GSAVE(:) !NCoord
53
    REAL(KREAL), SAVE :: ESET(MRESET)
54
    REAL(KREAL) :: ESET_tmp(MRESET), B(M2),BS(M2),BST(M2), B_tmp(M2) ! M2=256
55
      LOGICAL DEBUG, PRINT, ci_lt_zero
56
      INTEGER(KINT), SAVE :: MSET ! mth Iteration
57
    REAL(KREAL) :: ci(MRESET), ci_tmp(MRESET) ! MRESET = maximum number of iterations.
58
      INTEGER(KINT) :: NGEDIIS, MPLUS, INV, ITERA, MM, cis_zero
59
      INTEGER(KINT) :: I, J, K, JJ, JNV, II, IONE, IJ, IX, JX, KX
60
    INTEGER(KINT) :: current_size_B_mat, MyPointer
61
      REAL(KREAL) :: XMax, XNorm, DET, THRES, tmp, ER_star, ER_star_tmp
62

    
63
      DEBUG=.TRUE.
64
      PRINT=.FALSE.
65
    
66
      IF (PRINT)  WRITE(*,'(/,''      BEGIN GEDIIS   '')')
67
    
68
      ! Initialization
69
      IF (FRST) THEN
70
      ! FRST will be set to False in SPACE_GEDIIS, so no need to modify it here
71
         IF (ALLOCATED(GeomSet)) THEN
72
            IF (PRINT)  WRITE(*,'(/,''    In FRST, GEDIIS Dealloc  '')')
73
            DEALLOCATE(GeomSet,GradSet,DX,GSave)
74
            RETURN
75
         ELSE
76
            IF (PRINT)  WRITE(*,'(/,''     In FRST,  GEDIIS Alloc  '')')
77
            ALLOCATE(GeomSet(MRESET*NCoord),GradSet(MRESET*NCoord),DX(NCoord),GSAVE(NCoord))
78
         END IF
79
      END IF ! IF (FRST) THEN
80

    
81
      ! SPACE_GEDIIS SIMPLY LOADS THE CURRENT VALUES OF Geom AND Grad INTO THE ARRAYS GeomSet
82
      ! AND GradSet, MSET is set to zero and then 1 in SPACE_GEDIIS at first iteration.
83
      CALL SPACE_GEDIIS(MRESET,MSET,Geom,Grad,HEAT,NCoord,GeomSet,GradSet,ESET,FRST)
84

    
85
      IF (PRINT)  WRITE(*,'(/,''       GEDIIS after SPACE_GEDIIS  '')')
86

    
87
      ! INITIALIZE SOME VARIABLES AND CONSTANTS:
88
      NGEDIIS = MSET !MSET=mth iteration
89
      MPLUS = MSET + 1
90
      MM = MPLUS * MPLUS
91

    
92
      ! CONSTRUCT THE GEDIIS MATRIX:
93
      ! B_ij calculations from <B_ij=(g_i-g_j)(R_i-R_j)>
94
      JJ=0
95
      INV=-NCoord
96
      DO I=1,MSET
97
         INV=INV+NCoord
98
         JNV=-NCoord
99
         DO J=1,MSET
100
            JNV=JNV+NCoord
101
            JJ = JJ + 1
102
            B(JJ)=0.D0
103
      DO K=1, NCoord
104
         B(JJ) = B(JJ) + (((GradSet(INV+K)-GradSet(JNV+K))*(GeomSet(INV+K)-GeomSet(JNV+K)))/2.D0)
105
      END DO
106
         END DO
107
      END DO
108

    
109
     ! The following shifting is required to correct indices of B_ij elements in the GEDIIS matrix.
110
   ! The correction is needed because the last coloumn of the matrix contains all 1 and one zero.
111
      DO I=MSET-1,1,-1
112
         DO J=MSET,1,-1
113
            B(I*MSET+J+I) = B(I*MSET+J) 
114
         END DO
115
    END DO
116
   
117
      ! for last row and last column of GEDIIS matrix 
118
      DO I=1,MPLUS
119
         B(MPLUS*I) = 1.D0
120
         B(MPLUS*MSET+I) = 1.D0
121
      END DO
122
      B(MM) = 0.D0
123
    
124
    DO I=1, MPLUS
125
       !WRITE(*,'(10(1X,F20.4))') B((I-1)*MPLUS+1:I*(MPLUS))
126
    END DO
127
        
128
      ! ELIMINATE ERROR VECTORS WITH THE LARGEST NORM:
129
   80 CONTINUE
130
      DO I=1,MM !MM = (MSET+1) * (MSET+1)
131
         BS(I) = B(I) !just a copy of the original B (GEDIIS) matrix
132
      END DO
133
    
134
      IF (NGEDIIS .NE. MSET) THEN
135
        DO II=1,MSET-NGEDIIS
136
           XMAX = -1.D10
137
           ITERA = 0
138
           DO I=1,MSET
139
              XNORM = 0.D0
140
              INV = (I-1) * MPLUS
141
              DO J=1,MSET
142
                 XNORM = XNORM + ABS(B(INV + J))
143
              END DO
144
              IF (XMAX.LT.XNORM .AND. XNORM.NE.1.0D0) THEN
145
                 XMAX = XNORM
146
                 ITERA = I
147
                 IONE = INV + I
148
              ENDIF
149
           END DO
150
     
151
           DO I=1,MPLUS
152
              INV = (I-1) * MPLUS
153
              DO J=1,MPLUS
154
                 JNV = (J-1) * MPLUS
155
                 IF (J.EQ.ITERA) B(INV + J) = 0.D0
156
                 B(JNV + I) = B(INV + J)
157
              END DO
158
       END DO
159
           B(IONE) = 1.0D0
160
        END DO
161
    END IF ! matches IF (NGEDIIS .NE. MSET) THEN
162
    
163
      ! SCALE GEDIIS MATRIX BEFORE INVERSION:
164
      DO I=1,MPLUS
165
         II = MPLUS * (I-1) + I ! B(II)=diagonal elements of B matrix
166
         GSAVE(I) = 1.D0 / DSQRT(1.D-20+DABS(B(II)))
167
     !Print *, 'GSAVE(',I,')=', GSAVE(I) 
168
      END DO
169
      GSAVE(MPLUS) = 1.D0
170
      DO I=1,MPLUS
171
         DO J=1,MPLUS
172
            IJ = MPLUS * (I-1) + J
173
            B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J)
174
         END DO
175
      END DO
176
  
177
     ! INVERT THE GEDIIS MATRIX B:
178
    DO I=1, MPLUS
179
       !WRITE(*,'(10(1X,F20.4))') B((I-1)*MPLUS+1:I*(MPLUS))
180
    END DO
181
        
182
      CALL MINV(B,MPLUS,DET) ! matrix inversion.
183
    
184
    DO I=1, MPLUS
185
       !WRITE(*,'(10(1X,F20.16))') B((I-1)*MPLUS+1:I*(MPLUS))
186
    END DO
187
    
188
      DO I=1,MPLUS
189
         DO J=1,MPLUS
190
            IJ = MPLUS * (I-1) + J
191
            B(IJ) = B(IJ) * GSAVE(I) * GSAVE(J)
192
         END DO
193
      END DO
194
    
195
      ! COMPUTE THE NEW INTERPOLATED PARAMETER VECTOR (Geometry):
196
    ci=0.d0
197
    ci_tmp=0.d0
198
  
199
    ci_lt_zero= .FALSE.
200
    DO I=1, MSET
201
     DO J=1, MSET ! B matrix is read column-wise
202
        ci(I)=ci(I)+B((J-1)*(MPLUS)+I)*ESET(J) !ESET is energy set, yet to be fixed.
203
     END DO
204
     ci(I)=ci(I)+B((MPLUS-1)*(MPLUS)+I)
205
     !Print *, 'NO ci < 0 yet, c(',I,')=', ci(I)
206
     IF((ci(I) .LT. 0.0D0) .OR. (ci(I) .GT. 1.0D0)) THEN
207
       ci_lt_zero=.TRUE.
208
       EXIT
209
     END IF
210
      END DO !matches DO I=1, MSET
211
    
212
    IF (ci_lt_zero) Then
213
       cis_zero = 0
214
         ER_star = 0.D0
215
     ER_star_tmp = 1e32
216
     
217
     ! 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
         JJ=0
219
         INV=-NCoord
220
         DO IX=1,MSET
221
            INV=INV+NCoord
222
            JNV=-NCoord
223
            DO JX=1,MSET
224
               JNV=JNV+NCoord
225
               JJ = JJ + 1
226
               BST(JJ)=0.D0
227
           DO KX=1, NCoord
228
              BST(JJ) = BST(JJ) + (((GradSet(INV+KX)-GradSet(JNV+KX))*(GeomSet(INV+KX)-GeomSet(JNV+KX)))/2.D0)
229
           END DO
230
            END DO
231
       END DO  
232
    
233
     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
         ci(:)=1.D0
235
         ! find out which cis are zero in I:
236
       DO IX=1, MSET
237
          JJ=IAND(I, 2**(IX-1))
238
        IF(JJ .EQ. 0) Then
239
          ci(IX)=0.D0
240
          END IF
241
       END DO
242
       
243
       ci_lt_zero = .FALSE.
244
       ! 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
       DO IX=1, MSET*MSET
246
                B(IX) = BST(IX) !just a copy of the original B (GEDIIS) matrix
247
             END DO
248
       
249
             ! Removal of KXth row and KXth column in order to accomodate cI to be zero:
250
       current_size_B_mat=MSET
251
       cis_zero = 0
252
       ! The bits of I (index of the upper loop 'DO I=1, (2**MSET)-2'), gives which cis are zero.
253
       DO KX=1, MSET ! searching for each bit of I (index of the upper loop 'DO I=1, (2**MSET)-2')
254
          IF (ci(KX) .EQ. 0.D0) Then !remove KXth row and KXth column
255
           cis_zero = cis_zero + 1
256
           
257
             ! First row removal: (B matrix is read column-wise)
258
             JJ=0
259
                   DO IX=1,current_size_B_mat ! columns reading
260
                      DO JX=1,current_size_B_mat ! rows reading
261
                 IF (JX .NE. KX) Then
262
                     JJ = JJ + 1
263
                     B_tmp(JJ) = B((IX-1)*current_size_B_mat+JX)
264
                 END IF
265
              END DO   
266
             END DO
267
       
268
             DO IX=1,current_size_B_mat*(current_size_B_mat-1)
269
                B(IX) = B_tmp(IX)
270
             END DO
271
       
272
             ! Now column removal:
273
             JJ=0   
274
                   DO IX=1,KX-1 ! columns reading
275
                      DO JX=1,current_size_B_mat-1 ! rows reading
276
                 JJ = JJ + 1
277
                 B_tmp(JJ) = B(JJ)
278
              END DO
279
             END DO        
280
        
281
                   DO IX=KX+1,current_size_B_mat
282
                      DO JX=1,current_size_B_mat-1
283
                 JJ = JJ + 1
284
                    B_tmp(JJ) = B(JJ+current_size_B_mat-1)
285
              END DO
286
             END DO
287
              
288
             DO IX=1,(current_size_B_mat-1)*(current_size_B_mat-1)
289
                B(IX) = B_tmp(IX)
290
             END DO
291
           current_size_B_mat = current_size_B_mat - 1
292
        END IF ! matches IF (ci(KX) .EQ. 0.D0) Then !remove
293
           END DO ! matches DO KX=1, MSET
294

    
295
       ! The following shifting is required to correct indices of B_ij elements in the GEDIIS matrix.
296
       ! The correction is needed because the last coloumn and row of the matrix contains all 1 and one zero.
297
       DO IX=MSET-cis_zero-1,1,-1
298
        DO JX=MSET-cis_zero,1,-1
299
           B(IX*(MSET-cis_zero)+JX+IX) = B(IX*(MSET-cis_zero)+JX) 
300
        END DO
301
       END DO
302
       
303
       ! for last row and last column of GEDIIS matrix 
304
       DO IX=1,MPLUS-cis_zero
305
        B((MPLUS-cis_zero)*IX) = 1.D0
306
        B((MPLUS-cis_zero)*(MSET-cis_zero)+IX) = 1.D0
307
       END DO
308
       B((MPLUS-cis_zero) * (MPLUS-cis_zero)) = 0.D0
309
         
310
           DO IX=1, MPLUS
311
              !WRITE(*,'(10(1X,F20.4))') B((IX-1)*MPLUS+1:IX*(MPLUS))
312
           END DO
313
              
314
       ! ELIMINATE ERROR VECTORS WITH THE LARGEST NORM:
315
             IF (NGEDIIS .NE. MSET) THEN
316
          JX = min(MSET-NGEDIIS,MSET-cis_zero-1)
317
                DO II=1,JX
318
                   XMAX = -1.D10
319
                   ITERA = 0
320
                   DO IX=1,MSET-cis_zero
321
                      XNORM = 0.D0
322
                      INV = (IX-1) * (MPLUS-cis_zero)
323
                      DO J=1,MSET-cis_zero
324
                         XNORM = XNORM + ABS(B(INV + J))
325
                      END DO
326
                      IF (XMAX.LT.XNORM .AND. XNORM.NE.1.0D0) THEN
327
                         XMAX = XNORM
328
                         ITERA = IX
329
                         IONE = INV + IX
330
                      ENDIF
331
           END DO
332
     
333
                   DO IX=1,MPLUS-cis_zero
334
                      INV = (IX-1) * (MPLUS-cis_zero)
335
                      DO J=1,MPLUS-cis_zero
336
                         JNV = (J-1) * (MPLUS-cis_zero)
337
                         IF (J.EQ.ITERA) B(INV + J) = 0.D0
338
                         B(JNV + IX) = B(INV + J)
339
            END DO
340
               END DO
341
                   B(IONE) = 1.0D0
342
          END DO
343
           END IF ! matches IF (NGEDIIS .NE. MSET) THEN
344

    
345
       ! SCALE GEDIIS MATRIX BEFORE INVERSION:
346
       DO IX=1,MPLUS-cis_zero
347
        II = (MPLUS-cis_zero) * (IX-1) + IX ! B(II)=diagonal elements of B matrix
348
        GSAVE(IX) = 1.D0 / DSQRT(1.D-20+DABS(B(II)))
349
       END DO
350
       GSAVE(MPLUS-cis_zero) = 1.D0
351
       DO IX=1,MPLUS-cis_zero
352
        DO JX=1,MPLUS-cis_zero
353
           IJ = (MPLUS-cis_zero) * (IX-1) + JX
354
           B(IJ) = B(IJ) * GSAVE(IX) * GSAVE(JX)
355
        END DO
356
       END DO
357

    
358
       ! INVERT THE GEDIIS MATRIX B:    
359
       CALL MINV(B,MPLUS-cis_zero,DET) ! matrix inversion.
360
    
361
       DO IX=1,MPLUS-cis_zero
362
        DO JX=1,MPLUS-cis_zero
363
           IJ = (MPLUS-cis_zero) * (IX-1) + JX
364
           B(IJ) = B(IJ) * GSAVE(IX) * GSAVE(JX)
365
        END DO
366
       END DO
367
       
368
           DO IX=1, MPLUS
369
              !WRITE(*,'(10(1X,F20.4))') B((IX-1)*MPLUS+1:IX*(MPLUS))
370
           END DO
371
              
372
             ! ESET is rearranged to handle zero cis and stored in ESET_tmp:
373
       JJ=0
374
       DO IX=1, MSET
375
        IF (ci(IX) .NE. 0) Then
376
           JJ=JJ+1
377
           ESET_tmp(JJ) = ESET(IX)
378
        END IF
379
       END DO
380
       
381
       ! DETERMINATION OF nonzero cis:
382
       MyPointer=1
383
            DO IX=1, MSET-cis_zero
384
          tmp = 0.D0
385
            DO J=1, MSET-cis_zero ! B matrix is read column-wise
386
           tmp=tmp+B((J-1)*(MPLUS-cis_zero)+IX)*ESET_tmp(J)
387
        END DO
388
            tmp=tmp+B((MPLUS-cis_zero-1)*(MPLUS-cis_zero)+IX)
389
            IF((tmp .LT. 0.0D0) .OR. (tmp .GT. 1.0D0)) THEN
390
               ci_lt_zero=.TRUE.
391
               EXIT
392
        ELSE
393
           DO JX=MyPointer,MSET
394
              IF (ci(JX) .NE. 0) Then
395
                 ci(JX) = tmp
396
               MyPointer=JX+1
397
               EXIT
398
            END IF
399
           END DO
400
            END IF
401
             END DO !matches DO I=1, MSET-cis_zero
402
           !Print *, 'Local set of cis, first 10:, MSET=', MSET, ', I of (2**MSET)-2=', I
403
       !WRITE(*,'(10(1X,F20.4))') ci(1:MSET)
404
           !Print *, 'Local set of cis ends:****************************************'
405

    
406
             ! new set of cis determined based on the lower energy (ER_star):
407
       IF (.NOT. ci_lt_zero) Then
408
                Call Energy_GEDIIS(MRESET,MSET,ci,GeomSet,GradSet,ESET,NCoord,ER_star)
409
        IF (ER_star .LT. ER_star_tmp) Then      
410
           ci_tmp=ci  
411
           ER_star_tmp = ER_star
412
        END IF
413
             END IF ! matches IF (.NOT. ci_lt_zero) Then
414
          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
      ci = ci_tmp
416
    END IF! matches IF (ci_lt_zero) Then
417
    
418
    Print *, 'Final set of cis, first 10:***********************************'
419
    WRITE(*,'(10(1X,F20.4))') ci(1:MSET)
420
    Print *, 'Final set of cis ends:****************************************'
421
    Geom_new(:) = 0.D0
422
    DO I=1, MSET    
423
         Geom_new(:) = Geom_new(:) + (ci(I)*GeomSet((I-1)*NCoord+1:I*NCoord)) !MPLUS=MSET+1
424
     ! R_(N+1)=R*+DeltaR:
425
     DO J=1, NCoord
426
      tmp=0.D0
427
      DO K=1,NCoord
428
         !tmp=tmp+Hess((J-1)*NCoord+K)*GradSet((I-1)*NCoord+K) ! If Hinv=.False., then we need to invert Hess
429
      END DO
430
      Geom_new(J) = Geom_new(J) - (ci(I)*tmp)
431
     END DO
432
    END DO
433
    
434
    DX(:) = Geom(:) - Geom_new(:)
435
    
436
      XNORM = SQRT(DOT_PRODUCT(DX,DX))
437
      IF (PRINT) THEN
438
         WRITE (6,'(/10X,''DEVIATION IN X '',F10.4,8X,''DETERMINANT '',G9.3)') XNORM, DET
439
         !WRITE(*,'(10X,''GEDIIS COEFFICIENTS'')')
440
         !WRITE(*,'(10X,5F12.5)') (B(MPLUS*MSET+I),I=1,MSET)
441
      ENDIF
442

    
443
      ! THE FOLLOWING TOLERENCES FOR XNORM AND DET ARE SOMEWHAT ARBITRARY!
444
      THRES = MAX(10.D0**(-NCoord), 1.D-25)
445
      IF (XNORM.GT.2.D0 .OR. DABS(DET) .LT. THRES) THEN
446
         IF (PRINT)THEN
447
            WRITE(*,*) "THE GEDIIS MATRIX IS ILL CONDITIONED"     
448
            WRITE(*,*) " - PROBABLY, VECTORS ARE LINEARLY DEPENDENT - "
449
            WRITE(*,*) "THE GEDIIS STEP WILL BE REPEATED WITH A SMALLER SPACE"
450
         END IF
451
         DO K=1,MM
452
      B(K) = BS(K) ! why this is reverted? Because "IF (NGEDIIS .GT. 0) GO TO 80", see below
453
         END DO
454
         NGEDIIS = NGEDIIS - 1
455
         IF (NGEDIIS .GT. 0) GO TO 80
456
         IF (PRINT) WRITE(*,'(10X,''NEWTON-RAPHSON STEP TAKEN'')')
457
         Geom_new(:) = Geom(:) ! Geom_new is set to original Geom, thus DX = Geom(:) - Geom_new(:)=zero
458
      END IF ! matches IF (XNORM.GT.2.D0 .OR. DABS(DET).LT. THRES) THEN
459
    
460
   !*******************************************************************************************************************
461
    Geom_new(:) = 0.D0
462
    DO I=1, MSET    
463
         Geom_new(:) = Geom_new(:) + (ci(I)*GeomSet((I-1)*NCoord+1:I*NCoord)) !MPLUS=MSET+1
464
     ! R_(N+1)=R*+DeltaR:
465
     DO J=1, NCoord
466
      tmp=0.D0
467
      DO K=1,NCoord
468
         tmp=tmp+Hess((J-1)*NCoord+K)*GradSet((I-1)*NCoord+K) ! If Hinv=.False., then we need to invert Hess
469
      END DO
470
      Geom_new(J) = Geom_new(J) - (ci(I)*tmp)
471
     END DO
472
    END DO
473
   !*******************************************************************************************************************
474
    
475
      IF (PRINT)  WRITE(*,'(/,''       END GEDIIS  '',/)')
476

    
477
      END SUBROUTINE Step_GEDIIS
478