Statistiques
| Révision :

root / src / Step_RFO_all.f90 @ 12

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

1 1 pfleura2
SUBROUTINE Step_RFO_all(NCoord,Step,IGeom,Geom,Grad,Hess,Tangent)
2 1 pfleura2
3 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4 1 pfleura2
!
5 1 pfleura2
!This subroutine calculates new coordinates given a Hessian, the forces
6 1 pfleura2
! and the old coordinates
7 1 pfleura2
!
8 1 pfleura2
!!!!!!!!!!
9 1 pfleura2
! v1.0
10 1 pfleura2
! Uses only basic RFO step
11 1 pfleura2
!
12 1 pfleura2
!!!!!!!!!!
13 1 pfleura2
! v 2.0
14 1 pfleura2
! We add the test of ADF here, so that it should be more efficient.
15 1 pfleura2
! This version uses HInv to decide wether it should work with the Hessian
16 1 pfleura2
! or its inverse.
17 1 pfleura2
!
18 1 pfleura2
! v 3.0
19 1 pfleura2
! Uses DIIS. Done by P. Dayal.
20 1 pfleura2
!
21 1 pfleura2
! v3.1
22 1 pfleura2
! Back to origins ! We remove the ADF test here to see what we loose...
23 1 pfleura2
! untill of course its replacement by something more efficient... and free :)
24 1 pfleura2
!!!!!!!!!!!!!!!!!
25 1 pfleura2
!
26 1 pfleura2
! Input:
27 1 pfleura2
!   - NCoord: INTEGER(KINT), Number of degrees of freedom
28 1 pfleura2
!   - IGeom : INTEGER(KINT), Index of the geometry along the path
29 1 pfleura2
!   - Geom  : REAL(KREAL)(NCOORD), Geometry expressed in full coordinates
30 1 pfleura2
!   - Hess  : REAL(KREAL)(Ncoord,NCoord), Hessian at the current geometry
31 1 pfleura2
!
32 1 pfleura2
!
33 1 pfleura2
! Output:
34 1 pfleura2
!   - Step  : REAL(KREAL)(Ncoord), Calculated step
35 1 pfleura2
!
36 1 pfleura2
! In/Out:
37 1 pfleura2
!   - Tangent: REAL(KREAL)(Ncoord), Tangent to the path, at the current point
38 1 pfleura2
!             if Tangent=0, then we are optimizing a minimum,  tangent is not considered.
39 1 pfleura2
!               Input: Expressed in full coordinates.
40 1 pfleura2
!              Output: Replaced by the tangent expressed in Free vectors
41 1 pfleura2
! (Changes by PFL 3 Jan 2008)
42 1 pfleura2
!   -  Grad: READ(KREAL) (NCoord), Gradient at the current point
43 1 pfleura2
!               Input: Expressed in full coordinates.
44 1 pfleura2
! PFL 18 Jan 2008: Grad is no longer changed on output ->
45 1 pfleura2
!              Output: Replaced by the gradient expressed in Free vector, in the subspace orthogonal to the tangent.
46 1 pfleura2
! <- PFL 18 Jan 2008: Grad is no longer changed on output
47 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
48 1 pfleura2
49 12 pfleura2
!----------------------------------------------------------------------
50 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
51 12 pfleura2
!  Centre National de la Recherche Scientifique,
52 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
53 12 pfleura2
!
54 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
55 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
56 12 pfleura2
!
57 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
58 12 pfleura2
!  Contact: optnpath@gmail.com
59 12 pfleura2
!
60 12 pfleura2
! This file is part of "Opt'n Path".
61 12 pfleura2
!
62 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
63 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
64 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
65 12 pfleura2
!  or (at your option) any later version.
66 12 pfleura2
!
67 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
68 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
69 12 pfleura2
!
70 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
71 12 pfleura2
!  GNU Affero General Public License for more details.
72 12 pfleura2
!
73 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
74 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
75 12 pfleura2
!
76 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
77 12 pfleura2
! for commercial licensing opportunities.
78 12 pfleura2
!----------------------------------------------------------------------
79 12 pfleura2
80 1 pfleura2
  use Io_module, only : IoOut
81 1 pfleura2
82 12 pfleura2
  use Path_module, only :  Hinv,Vfree
83 1 pfleura2
  ! VFree(Ncoord,Ncoord)
84 1 pfleura2
85 1 pfleura2
  IMPLICIT NONE
86 1 pfleura2
87 1 pfleura2
  INTEGER, PARAMETER :: KINT=KIND(1)
88 1 pfleura2
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
89 1 pfleura2
90 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: NCoord,IGeom
91 1 pfleura2
  REAL(KREAL), INTENT(IN) :: Hess(NCoord,NCoord)
92 1 pfleura2
  REAL(KREAL), INTENT(IN) :: Grad(NCoord),Geom(NCoord)
93 1 pfleura2
  REAL(KREAL), INTENT(INOUT) :: Tangent(Ncoord) ! Destroyed on output
94 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: Step(NCoord)
95 1 pfleura2
96 1 pfleura2
  INTEGER(KINT) :: NFree
97 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: eigval(:), eigvec(:,:), eigvli(:)
98 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: Tanf(:)
99 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: Grad_f(:),Step_f(:) ! NFree
100 1 pfleura2
101 1 pfleura2
  REAL(KREAL), PARAMETER :: tiny=1e-20, zero=0., dele3=1e-6, eps=1e-12
102 1 pfleura2
  REAL(KREAL), PARAMETER :: crit=1e-8
103 2 pfleura2
  INTEGER(KINT) :: i, j, idx, k, isch
104 2 pfleura2
  REAL(KREAL) :: grd, eval, norm
105 2 pfleura2
  REAL(KREAL) :: dx
106 2 pfleura2
  CHARACTER(120) :: fmt2
107 1 pfleura2
108 1 pfleura2
  LOGICAL :: Debug
109 1 pfleura2
110 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: HFree(:,:) ! NFree,NFree
111 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: Htmp(:,:) ! NCoord,NFree
112 1 pfleura2
113 2 pfleura2
!  LOGICAL, SAVE :: LFirst=.TRUE.
114 1 pfleura2
115 1 pfleura2
  INTERFACE
116 1 pfleura2
     function valid(string) result (isValid)
117 1 pfleura2
       CHARACTER(*), intent(in) :: string
118 1 pfleura2
       logical                  :: isValid
119 1 pfleura2
     END function VALID
120 1 pfleura2
  END INTERFACE
121 1 pfleura2
122 1 pfleura2
  debug=valid("step_rfo_all")
123 1 pfleura2
  if (debug) WRITE(*,*) "=========================== Entering Step_RFO_All ===================="
124 1 pfleura2
  if (debug) WRITE(*,*) "=========================== IGeom=",IGeom," ===================="
125 1 pfleura2
126 1 pfleura2
! PFL 22.Nov.2007 ->
127 1 pfleura2
! Nfree is equal to Ncoord-1 only when optimizing in the plane
128 1 pfleura2
! orthogonal to the tangent.
129 1 pfleura2
! In the case of a regular opt, NFree=Ncoord.
130 1 pfleura2
! Next line has been moved later
131 1 pfleura2
!  NFree=Ncoord-1
132 1 pfleura2
! <- PFL 22.Nov.2007
133 1 pfleura2
134 1 pfleura2
  IF (debug) THEN
135 1 pfleura2
     WRITE(*,*) 'DBG Step_RFO_All Hess'
136 1 pfleura2
     WRITE(*,*) 'DBG Step_RFO_All NCoord=',NCoord
137 1 pfleura2
138 1 pfleura2
     Idx=min(12,NCoord)
139 1 pfleura2
     DO I=1,NCoord
140 1 pfleura2
        WRITE(*,'(12(1X,F10.4))') Hess(I,1:Idx)
141 1 pfleura2
     END DO
142 1 pfleura2
     WRITE(*,*) 'DBG Step_RFO_All Grad'
143 1 pfleura2
     WRITE(*,'(12(1X,F10.4))') Grad(1:Idx)
144 1 pfleura2
     WRITE(*,*) 'DBG Step_RFO_All Coord'
145 1 pfleura2
     WRITE(*,'(12(1X,F10.4))') Geom(1:Idx)
146 1 pfleura2
     WRITE(*,*) 'DBG Step_RFO_All Tangent'
147 1 pfleura2
     WRITE(*,'(12(1X,F10.4))') tangent(1:Idx)
148 1 pfleura2
149 1 pfleura2
  END IF
150 1 pfleura2
151 1 pfleura2
  Call FreeMv(NCoord,Vfree) ! VFree(Ncoord,Ncoord)
152 1 pfleura2
! we orthogonalize Vfree to the tangent vector of this geom
153 1 pfleura2
! 2007/05/29 Only if Tangent/=0.d0
154 1 pfleura2
  Norm=sqrt(dot_product(Tangent,Tangent))
155 1 pfleura2
  IF (Norm.GT.eps) THEN
156 1 pfleura2
     ALLOCATE(Tanf(NCoord))
157 1 pfleura2
158 1 pfleura2
     ! We normalize Tangent
159 1 pfleura2
     Tangent=Tangent/Norm
160 1 pfleura2
161 1 pfleura2
     ! We convert Tangent into vfree only displacements
162 1 pfleura2
     ! This is useless for now (2007.Apr.23) as vfree=Id matrix
163 1 pfleura2
     ! but it will be usefull as soon as we introduce Constraints
164 1 pfleura2
     DO I=1,NCoord
165 1 pfleura2
        Tanf(I)=dot_product(reshape(vfree(:,I),(/NCoord/)),Tangent)
166 1 pfleura2
     END DO
167 1 pfleura2
     Tangent=0.d0
168 1 pfleura2
     DO I=1,NCoord
169 1 pfleura2
        Tangent=Tangent+Tanf(i)*vfree(:,I)
170 1 pfleura2
     END DO
171 1 pfleura2
172 1 pfleura2
     ! first we substract Tangent from vfree
173 1 pfleura2
     DO I=1,NCoord
174 1 pfleura2
        Norm=dot_product(reshape(vfree(:,i),(/NCoord/)),Tangent)
175 1 pfleura2
        Vfree(:,I)=vfree(:,i)-Norm*Tangent
176 1 pfleura2
     END DO
177 1 pfleura2
178 8 pfleura2
     Idx=0
179 1 pfleura2
     ! Schmidt orthogonalization of the vfree vectors
180 1 pfleura2
     DO I=1,NCoord
181 1 pfleura2
        ! We substract the first vectors
182 1 pfleura2
        ! we do it twice as the Schmidt procedure is not numerically stable
183 1 pfleura2
        DO isch=1,2
184 1 pfleura2
           DO J=1,Idx
185 1 pfleura2
              Norm=dot_product(reshape(vfree(:,I),(/NCoord/)),reshape(vfree(:,J),(/NCoord/)))
186 1 pfleura2
              vfree(:,I)=vfree(:,I)-Norm*vfree(:,J)
187 1 pfleura2
           END DO
188 1 pfleura2
        END DO
189 1 pfleura2
        Norm=dot_product(reshape(vfree(:,I),(/NCoord/)),reshape(vfree(:,I),(/NCoord/)))
190 1 pfleura2
        IF (Norm.GE.crit) THEN
191 1 pfleura2
           idx=idx+1
192 1 pfleura2
           vfree(:,idx)=vfree(:,i)/sqrt(Norm)
193 1 pfleura2
        END IF
194 1 pfleura2
     END DO
195 1 pfleura2
196 1 pfleura2
     If (Idx/= NCoord-1) THEN
197 1 pfleura2
        WRITE(*,*) "Pb in orthogonalizing vfree to tangent for geom",IGeom
198 1 pfleura2
        WRITE(Ioout,*) "Pb in orthogonalizing vfree to tangent for geom",IGeom
199 1 pfleura2
        STOP
200 1 pfleura2
     END IF
201 1 pfleura2
202 2 pfleura2
     if (debug) WRITE(*,*) "Deallocating Tanf"
203 1 pfleura2
     DEALLOCATE(Tanf)
204 1 pfleura2
205 1 pfleura2
     NFree=Idx
206 1 pfleura2
207 1 pfleura2
  ELSE ! Tangent =0, matches IF (Norm.GT.eps) THEN
208 1 pfleura2
     if (debug) WRITE(*,*) "Tangent=0, using full displacement"
209 1 pfleura2
     NFree=NCoord
210 1 pfleura2
  END IF !IF (Norm.GT.eps) THEN
211 1 pfleura2
212 1 pfleura2
  if (debug) WRITE(*,*) 'DBG Step_RFO_All NFree=',NFree
213 1 pfleura2
214 1 pfleura2
215 1 pfleura2
! We now calculate the new step
216 1 pfleura2
! we project the hessian onto the free vectors
217 1 pfleura2
     ALLOCATE(hfree(NFree,NFree),htmp(NCoord,NFree),Grad_f(NFree),Step_f(NFree))
218 1 pfleura2
     DO J=1,NFree
219 1 pfleura2
        DO I=1,NCoord
220 1 pfleura2
           Htmp(I,J)=0.d0
221 1 pfleura2
           DO K=1,NCoord
222 1 pfleura2
              Htmp(I,J)=htmp(I,J)+Hess(I,K)*vfree(K,J)
223 1 pfleura2
           END DO
224 1 pfleura2
        END DO
225 1 pfleura2
     END DO
226 1 pfleura2
     DO J=1,NFree
227 1 pfleura2
        DO I=1,NFree
228 1 pfleura2
           HFree(i,j)=0.d0
229 1 pfleura2
           DO K=1,NCoord
230 1 pfleura2
              HFree(i,j)=hfree(i,j)+vfree(k,i)*htmp(k,j)
231 1 pfleura2
           END DO
232 1 pfleura2
        END DO
233 1 pfleura2
     END DO
234 1 pfleura2
235 1 pfleura2
! We diagonalize the hessian or its inverse
236 1 pfleura2
  ALLOCATE(eigval(NFree), eigvec(NFree,NFree), eigvli(NFree))
237 1 pfleura2
238 1 pfleura2
  call Jacobi(Hfree,NFree,eigvli,eigvec,NFree)
239 1 pfleura2
240 1 pfleura2
  if (debug) THEN
241 1 pfleura2
     WRITE(*,*) 'Eigensystem, Step_RFO_all.f90, L225'
242 1 pfleura2
     fmt2='(I5,":",F8.3," -",  (1X,F10.4))'
243 1 pfleura2
     WRITE(fmt2(19:20),'(I2)') min(NFree,99)
244 1 pfleura2
     DO I=1,NFree
245 1 pfleura2
        WRITE(*,fmt2) I,Eigvli(I),eigvec(:,I)
246 1 pfleura2
     END DO
247 1 pfleura2
  END IF
248 1 pfleura2
249 1 pfleura2
  ! We inverse the eigenvalues if Hess corresponds to Hessian inverse
250 1 pfleura2
  IF (Hinv) THEN
251 1 pfleura2
     do J=1,NFree
252 1 pfleura2
        if (abs(eigvli(j)) <= tiny) eigvli(j) = zero
253 1 pfleura2
        eigval(j) = sign (eigvli(j)**2 / (dele3 + abs(eigvli(j))**3), eigvli(j))
254 1 pfleura2
        if (abs(eigval(j)) <= tiny) eigval(j) = zero
255 1 pfleura2
     end do
256 1 pfleura2
  ELSE
257 1 pfleura2
     eigval=eigvli
258 1 pfleura2
  END IF
259 1 pfleura2
260 1 pfleura2
  call trie(NFree,eigval,eigvec,NFree)
261 1 pfleura2
262 1 pfleura2
  DO I=1,NFree
263 1 pfleura2
     Grad_f(I)=dot_product(reshape(vfree(:,I),(/NCoord/)),grad)
264 1 pfleura2
  END DO
265 1 pfleura2
266 1 pfleura2
  ! We now construct the step
267 1 pfleura2
268 1 pfleura2
  Step_f=0.d0
269 1 pfleura2
  DO I=1,NFree
270 1 pfleura2
     grd= dot_product(grad_f,reshape(eigvec(:,i),(/NFree/)))
271 1 pfleura2
     eval = 0.5 * (abs(eigval(i)) + sqrt (eigval(i)**2 + 4.*grd**2))
272 1 pfleura2
     dx   = (-grd) / eval
273 1 pfleura2
     step_f = step_f + dx * eigvec(:,i)
274 1 pfleura2
     if (debug) write (*,*) i,eigval(i),eval,grd,dx
275 1 pfleura2
  END DO
276 1 pfleura2
277 1 pfleura2
  Step=0.d0
278 1 pfleura2
! PFL 04 Apr 2008 ->
279 1 pfleura2
! Grad is once again modified
280 1 pfleura2
!  Grad=0.d0
281 1 pfleura2
  DO I=1,NFree
282 1 pfleura2
     Step=Step+ step_f(i)*vfree(:,i)
283 1 pfleura2
!     Grad=Grad+ Grad_f(i)*vfree(:,i)
284 1 pfleura2
  END DO
285 1 pfleura2
! <- PFL 04 Apr 2008
286 1 pfleura2
287 2 pfleura2
  if (debug) WRITE(*,*) "Deallocataing Eigval"
288 2 pfleura2
  DEALLOCATE(eigval)
289 2 pfleura2
  if (debug) WRITE(*,*) "Deallocataing Eigvec"
290 2 pfleura2
  DEALLOCATE(eigvec)
291 2 pfleura2
  if (debug) WRITE(*,*) "Deallocataing Eigvli"
292 2 pfleura2
  DEALLOCATE(eigvli)
293 2 pfleura2
  if (debug) WRITE(*,*) "Deallocataing hfree"
294 2 pfleura2
  DEALLOCATE(hfree)
295 2 pfleura2
  if (debug) WRITE(*,*) "Deallocataing htmp"
296 2 pfleura2
  DEALLOCATE(htmp)
297 2 pfleura2
  if (debug) WRITE(*,*) "Deallocataing grad_f"
298 2 pfleura2
  DEALLOCATE(grad_f)
299 2 pfleura2
  if (debug) WRITE(*,*) "Deallocataing step_f"
300 2 pfleura2
  DEALLOCATE(step_f)
301 1 pfleura2
302 1 pfleura2
  if (debug) THEN
303 1 pfleura2
     WRITE(*,*) 'DBG Step_RFO_All Step'
304 1 pfleura2
     WRITE(*,'(12(1X,F8.4))') Step(1:Idx)
305 1 pfleura2
  END IF
306 1 pfleura2
307 1 pfleura2
  if (debug) WRITE(*,*) "=========================== Step_RFO_All Over ===================="
308 1 pfleura2
309 1 pfleura2
END SUBROUTINE STEP_RFO_ALL
310 1 pfleura2