Statistiques
| Révision :

root / src / Step_RFO_all.f90

Historique | Voir | Annoter | Télécharger (9,66 ko)

1
SUBROUTINE Step_RFO_all(NCoord,Step,IGeom,Geom,Grad,Hess,Tangent)
2

    
3
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4
!
5
!This subroutine calculates new coordinates given a Hessian, the forces
6
! and the old coordinates
7
!
8
!!!!!!!!!!
9
! v1.0
10
! Uses only basic RFO step
11
!
12
!!!!!!!!!!
13
! v 2.0
14
! We add the test of ADF here, so that it should be more efficient.
15
! This version uses HInv to decide wether it should work with the Hessian
16
! or its inverse.
17
!
18
! v 3.0
19
! Uses DIIS. Done by P. Dayal.
20
!
21
! v3.1
22
! Back to origins ! We remove the ADF test here to see what we loose...
23
! untill of course its replacement by something more efficient... and free :)
24
!!!!!!!!!!!!!!!!!
25
!
26
! Input:
27
!   - NCoord: INTEGER(KINT), Number of degrees of freedom
28
!   - IGeom : INTEGER(KINT), Index of the geometry along the path
29
!   - Geom  : REAL(KREAL)(NCOORD), Geometry expressed in full coordinates
30
!   - Hess  : REAL(KREAL)(Ncoord,NCoord), Hessian at the current geometry
31
!  
32
!
33
! Output:
34
!   - Step  : REAL(KREAL)(Ncoord), Calculated step
35
!
36
! In/Out:
37
!   - Tangent: REAL(KREAL)(Ncoord), Tangent to the path, at the current point
38
!             if Tangent=0, then we are optimizing a minimum,  tangent is not considered.
39
!               Input: Expressed in full coordinates.
40
!              Output: Replaced by the tangent expressed in Free vectors
41
! (Changes by PFL 3 Jan 2008)
42
!   -  Grad: READ(KREAL) (NCoord), Gradient at the current point
43
!               Input: Expressed in full coordinates.
44
! PFL 18 Jan 2008: Grad is no longer changed on output ->
45
!              Output: Replaced by the gradient expressed in Free vector, in the subspace orthogonal to the tangent.
46
! <- PFL 18 Jan 2008: Grad is no longer changed on output
47
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
48

    
49
!----------------------------------------------------------------------
50
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
51
!  Centre National de la Recherche Scientifique,
52
!  Université Claude Bernard Lyon 1. All rights reserved.
53
!
54
!  This work is registered with the Agency for the Protection of Programs 
55
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
56
!
57
!  Authors: P. Fleurat-Lessard, P. Dayal
58
!  Contact: optnpath@gmail.com
59
!
60
! This file is part of "Opt'n Path".
61
!
62
!  "Opt'n Path" is free software: you can redistribute it and/or modify
63
!  it under the terms of the GNU Affero General Public License as
64
!  published by the Free Software Foundation, either version 3 of the License,
65
!  or (at your option) any later version.
66
!
67
!  "Opt'n Path" is distributed in the hope that it will be useful,
68
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
69
!
70
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
71
!  GNU Affero General Public License for more details.
72
!
73
!  You should have received a copy of the GNU Affero General Public License
74
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
75
!
76
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
77
! for commercial licensing opportunities.
78
!----------------------------------------------------------------------
79

    
80
  use Io_module, only : IoOut
81
  
82
  use Path_module, only :  Hinv,Vfree
83
  ! VFree(Ncoord,Ncoord)
84

    
85
  IMPLICIT NONE
86

    
87
  INTEGER, PARAMETER :: KINT=KIND(1)
88
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
89

    
90
  INTEGER(KINT), INTENT(IN) :: NCoord,IGeom
91
  REAL(KREAL), INTENT(IN) :: Hess(NCoord,NCoord)
92
  REAL(KREAL), INTENT(IN) :: Grad(NCoord),Geom(NCoord)
93
  REAL(KREAL), INTENT(INOUT) :: Tangent(Ncoord) ! Destroyed on output
94
  REAL(KREAL), INTENT(OUT) :: Step(NCoord)
95

    
96
  INTEGER(KINT) :: NFree
97
  REAL(KREAL), ALLOCATABLE :: eigval(:), eigvec(:,:), eigvli(:)
98
  REAL(KREAL), ALLOCATABLE :: Tanf(:)
99
  REAL(KREAL), ALLOCATABLE :: Grad_f(:),Step_f(:) ! NFree
100

    
101
  REAL(KREAL), PARAMETER :: tiny=1e-20, zero=0., dele3=1e-6, eps=1e-12
102
  REAL(KREAL), PARAMETER :: crit=1e-8
103
  INTEGER(KINT) :: i, j, idx, k, isch
104
  REAL(KREAL) :: grd, eval, norm
105
  REAL(KREAL) :: dx
106
  CHARACTER(120) :: fmt2
107

    
108
  LOGICAL :: Debug
109

    
110
  REAL(KREAL), ALLOCATABLE :: HFree(:,:) ! NFree,NFree
111
  REAL(KREAL), ALLOCATABLE :: Htmp(:,:) ! NCoord,NFree
112

    
113
!  LOGICAL, SAVE :: LFirst=.TRUE.
114

    
115
  INTERFACE
116
     function valid(string) result (isValid)
117
       CHARACTER(*), intent(in) :: string
118
       logical                  :: isValid
119
     END function VALID
120
  END INTERFACE
121

    
122
  debug=valid("step_rfo_all")
123
  if (debug) WRITE(*,*) "=========================== Entering Step_RFO_All ===================="
124
  if (debug) WRITE(*,*) "=========================== IGeom=",IGeom," ===================="
125

    
126
! PFL 22.Nov.2007 ->
127
! Nfree is equal to Ncoord-1 only when optimizing in the plane
128
! orthogonal to the tangent. 
129
! In the case of a regular opt, NFree=Ncoord. 
130
! Next line has been moved later
131
!  NFree=Ncoord-1
132
! <- PFL 22.Nov.2007
133

    
134
  IF (debug) THEN
135
     WRITE(*,*) 'DBG Step_RFO_All Hess'
136
     WRITE(*,*) 'DBG Step_RFO_All NCoord=',NCoord
137

    
138
     Idx=min(12,NCoord)
139
     DO I=1,NCoord
140
        WRITE(*,'(12(1X,F10.4))') Hess(I,1:Idx)
141
     END DO
142
     WRITE(*,*) 'DBG Step_RFO_All Grad'
143
     WRITE(*,'(12(1X,F10.4))') Grad(1:Idx)
144
     WRITE(*,*) 'DBG Step_RFO_All Coord'
145
     WRITE(*,'(12(1X,F10.4))') Geom(1:Idx)
146
     WRITE(*,*) 'DBG Step_RFO_All Tangent'
147
     WRITE(*,'(12(1X,F10.4))') tangent(1:Idx)
148

    
149
  END IF
150

    
151
  Call FreeMv(NCoord,Vfree) ! VFree(Ncoord,Ncoord)
152
! we orthogonalize Vfree to the tangent vector of this geom
153
! 2007/05/29 Only if Tangent/=0.d0
154
  Norm=sqrt(dot_product(Tangent,Tangent))
155
  IF (Norm.GT.eps) THEN
156
     ALLOCATE(Tanf(NCoord))
157

    
158
     ! We normalize Tangent
159
     Tangent=Tangent/Norm
160

    
161
     ! We convert Tangent into vfree only displacements
162
     ! This is useless for now (2007.Apr.23) as vfree=Id matrix
163
     ! but it will be usefull as soon as we introduce Constraints
164
     DO I=1,NCoord
165
        Tanf(I)=dot_product(reshape(vfree(:,I),(/NCoord/)),Tangent)
166
     END DO
167
     Tangent=0.d0
168
     DO I=1,NCoord
169
        Tangent=Tangent+Tanf(i)*vfree(:,I)
170
     END DO
171

    
172
     ! first we substract Tangent from vfree
173
     DO I=1,NCoord
174
        Norm=dot_product(reshape(vfree(:,i),(/NCoord/)),Tangent)
175
        Vfree(:,I)=vfree(:,i)-Norm*Tangent
176
     END DO
177

    
178
     Idx=0
179
     ! Schmidt orthogonalization of the vfree vectors
180
     DO I=1,NCoord
181
        ! We substract the first vectors
182
        ! 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
     If (Idx/= NCoord-1) THEN
197
        WRITE(*,*) "Pb in orthogonalizing vfree to tangent for geom",IGeom
198
        WRITE(Ioout,*) "Pb in orthogonalizing vfree to tangent for geom",IGeom
199
        STOP
200
     END IF
201
     
202
     if (debug) WRITE(*,*) "Deallocating Tanf"
203
     DEALLOCATE(Tanf)
204

    
205
     NFree=Idx
206

    
207
  ELSE ! Tangent =0, matches IF (Norm.GT.eps) THEN
208
     if (debug) WRITE(*,*) "Tangent=0, using full displacement"
209
     NFree=NCoord
210
  END IF !IF (Norm.GT.eps) THEN
211
  
212
  if (debug) WRITE(*,*) 'DBG Step_RFO_All NFree=',NFree
213
  
214

    
215
! We now calculate the new step
216
! we project the hessian onto the free vectors
217
     ALLOCATE(hfree(NFree,NFree),htmp(NCoord,NFree),Grad_f(NFree),Step_f(NFree))
218
     DO J=1,NFree
219
        DO I=1,NCoord
220
           Htmp(I,J)=0.d0
221
           DO K=1,NCoord
222
              Htmp(I,J)=htmp(I,J)+Hess(I,K)*vfree(K,J)
223
           END DO
224
        END DO
225
     END DO
226
     DO J=1,NFree
227
        DO I=1,NFree
228
           HFree(i,j)=0.d0
229
           DO K=1,NCoord
230
              HFree(i,j)=hfree(i,j)+vfree(k,i)*htmp(k,j)
231
           END DO
232
        END DO
233
     END DO
234

    
235
! We diagonalize the hessian or its inverse
236
  ALLOCATE(eigval(NFree), eigvec(NFree,NFree), eigvli(NFree)) 
237

    
238
  call Jacobi(Hfree,NFree,eigvli,eigvec,NFree)
239

    
240
  if (debug) THEN
241
     WRITE(*,*) 'Eigensystem, Step_RFO_all.f90, L225'
242
     fmt2='(I5,":",F8.3," -",  (1X,F10.4))'
243
     WRITE(fmt2(19:20),'(I2)') min(NFree,99)
244
     DO I=1,NFree
245
        WRITE(*,fmt2) I,Eigvli(I),eigvec(:,I)
246
     END DO
247
  END IF
248

    
249
  ! We inverse the eigenvalues if Hess corresponds to Hessian inverse
250
  IF (Hinv) THEN
251
     do J=1,NFree
252
        if (abs(eigvli(j)) <= tiny) eigvli(j) = zero
253
        eigval(j) = sign (eigvli(j)**2 / (dele3 + abs(eigvli(j))**3), eigvli(j))
254
        if (abs(eigval(j)) <= tiny) eigval(j) = zero
255
     end do
256
  ELSE
257
     eigval=eigvli
258
  END IF
259

    
260
  call trie(NFree,eigval,eigvec,NFree)
261

    
262
  DO I=1,NFree
263
     Grad_f(I)=dot_product(reshape(vfree(:,I),(/NCoord/)),grad)
264
  END DO
265

    
266
  ! We now construct the step
267

    
268
  Step_f=0.d0
269
  DO I=1,NFree
270
     grd= dot_product(grad_f,reshape(eigvec(:,i),(/NFree/)))
271
     eval = 0.5 * (abs(eigval(i)) + sqrt (eigval(i)**2 + 4.*grd**2))
272
     dx   = (-grd) / eval
273
     step_f = step_f + dx * eigvec(:,i)
274
     if (debug) write (*,*) i,eigval(i),eval,grd,dx
275
  END DO
276

    
277
  Step=0.d0
278
! PFL 04 Apr 2008 -> 
279
! Grad is once again modified
280
!  Grad=0.d0
281
  DO I=1,NFree
282
     Step=Step+ step_f(i)*vfree(:,i)
283
!     Grad=Grad+ Grad_f(i)*vfree(:,i)
284
  END DO
285
! <- PFL 04 Apr 2008
286
     
287
  if (debug) WRITE(*,*) "Deallocataing Eigval"
288
  DEALLOCATE(eigval) 
289
  if (debug) WRITE(*,*) "Deallocataing Eigvec"
290
  DEALLOCATE(eigvec) 
291
  if (debug) WRITE(*,*) "Deallocataing Eigvli"
292
  DEALLOCATE(eigvli) 
293
  if (debug) WRITE(*,*) "Deallocataing hfree"
294
  DEALLOCATE(hfree) 
295
  if (debug) WRITE(*,*) "Deallocataing htmp"
296
  DEALLOCATE(htmp) 
297
  if (debug) WRITE(*,*) "Deallocataing grad_f"
298
  DEALLOCATE(grad_f) 
299
  if (debug) WRITE(*,*) "Deallocataing step_f"
300
  DEALLOCATE(step_f) 
301

    
302
  if (debug) THEN
303
     WRITE(*,*) 'DBG Step_RFO_All Step'
304
     WRITE(*,'(12(1X,F8.4))') Step(1:Idx)
305
  END IF
306

    
307
  if (debug) WRITE(*,*) "=========================== Step_RFO_All Over ===================="        
308

    
309
END SUBROUTINE STEP_RFO_ALL
310

    
311