Statistiques
| Révision :

root / src / Extrapol_baker.f90

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

1
SUBROUTINE Extrapol_baker(s,dist,x0,y0,z0,xgeom,Coef,XgeomF)
2

    
3
  ! This subroutine constructs the path, andabscissa if dist<>Infinity, it samples
4
  ! the path to obtain geometries.
5
  ! Basically, you call it twice: i) dist=infinity, it will calculate the length of the path
6
  ! ii) dist finite, it will give you the images you want along the path.
7
  !
8
  ! For now, it gives equidistant geometries.
9
  !
10
  ! A reference geometry for the alignment: X0(Nat),Y0(Nat),Z0(Nat)
11

    
12
!----------------------------------------------------------------------
13
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
14
!  Centre National de la Recherche Scientifique,
15
!  Université Claude Bernard Lyon 1. All rights reserved.
16
!
17
!  This work is registered with the Agency for the Protection of Programs 
18
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
19
!
20
!  Authors: P. Fleurat-Lessard, P. Dayal
21
!  Contact: optnpath@gmail.com
22
!
23
! This file is part of "Opt'n Path".
24
!
25
!  "Opt'n Path" is free software: you can redistribute it and/or modify
26
!  it under the terms of the GNU Affero General Public License as
27
!  published by the Free Software Foundation, either version 3 of the License,
28
!  or (at your option) any later version.
29
!
30
!  "Opt'n Path" is distributed in the hope that it will be useful,
31
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
32
!
33
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
34
!  GNU Affero General Public License for more details.
35
!
36
!  You should have received a copy of the GNU Affero General Public License
37
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
38
!
39
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
40
! for commercial licensing opportunities.
41
!----------------------------------------------------------------------
42

    
43
  use Path_module, only : IntCoordI, NMaxPtPath, XyzGeomF, IntCoordF, &
44
       IntTangent, Renum, Nom, Order, MassAt, SGeom, Nat, NGeomI, &
45
       NGeomF, Atome, NCoord, OrderInv, XyzGeomI,BTransInvF, &
46
       XPrimitive,XPrimitiveF, NPrim,                                      &
47
       BTransInv_local,UMatF,UMat_local,FirstTimePathCreate,Pi
48
  ! IntCoordI(NGeomI,3*Nat-6), Coef(NGeomI,NCoord), NMaxPtPath=1000 (default value)
49
  ! More appropriate: IntCoordI(NGeomI,NCoord)
50
  use Io_module
51
  IMPLICIT NONE
52

    
53
  REAL(KREAL), INTENT(OUT) :: s
54
  ! A reference geometry for the alignment:
55
  REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat)
56
  ! Xgeom(NGeomI): abscissa of all initial geometries.
57
  ! Coef(NGeomI,NCoord): spline coefficients.
58
  REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord)
59
  ! Number of the cycles for the optimization:
60
  ! XGeomF(NGeomF): Final geometries.
61
  REAL(KREAL), INTENT(OUT) :: XGeomF(NGeomF)
62

    
63
  INTEGER(KINT) :: IdxGeom, I, J, K
64
  REAL(KREAL) :: Rmsd,MRot(3,3), ds, u, v
65

    
66
  REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:), DerInt(:) ! (Nat,3)
67
  REAL(KREAL), ALLOCATABLE :: Xyz_k(:,:) ! (Nat,3)
68
  REAL(KREAL), ALLOCATABLE :: IntCoord_interpol(:) ! (3*Nat-6)
69
  REAL(KREAL), ALLOCATABLE :: IntCoord_k(:) ! (3*Nat-6)
70
  REAL(KREAL), ALLOCATABLE :: XPrimRef(:),XPrim(:) ! NPrim
71

    
72
  LOGICAL ::  debug, print,printspline
73
  LOGICAL, EXTERNAL :: valid
74

    
75
  INTEGER(KINT) :: NSpline
76

    
77

    
78
  ! We will calculate the length of the path, in MW coordinates...
79
  ! this is done in a stupid way: we interpolate the Baker coordinates values,
80
  ! convert them into cartesian, weight the cartesian
81
  ! and calculate the evolution of the distance ! 
82
  ! We have to follow the same procedure for every geometry,
83
  ! so even for the first one, we have to convert it from internal Baker 
84
  ! coordinates to cartesian !
85

    
86
  debug=valid("Extrapol_baker")
87
  print=valid("printgeom")
88
  printspline=(valid("printspline").AND.(dist<=1e30))
89

    
90
  if (debug) WRITE(*,*) "================= Entering Extrapol_baker ===================="
91
  if (debug) WRITE(*,*) "DBG Extrapol_baker dist=",Dist
92
  NSpline=int(NMaxPtPath/100)
93
  !IF (printspline) THEN
94
  !  WRITE(TmpChar,'(I5)') Iopt
95
  ! FileSpline=Trim(adjustL(PathName)) // '_spline.' // AdjustL(TRIM(TmpChar))
96
  !OPEN(IOTMP,FILE=FileSpline)
97
  ! END IF
98

    
99
  ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),IntCoord_interpol(NCoord),DerInt(NCoord))
100
  ALLOCATE(IntCoord_k(NCoord),Xyz_k(Nat,3))
101
  ALLOCATE(XPrimRef(NPrim),XPrim(NPrim))
102

    
103
  ! XyzGeomI(:,:,:) ! (NGeomI,3,Nat)
104
  ! IntCoordI(:,:) ! (NGeomI,3*Nat-6)
105

    
106
  !XyzGeomF(1,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
107
  XyzGeomF(1,:,:)=XyzGeomI(1,:,:) ! 1st index is geometry-index.
108
  IntCoordF(1,:)=IntCoordI(1,:)
109

    
110
  ! We calculate the first derivatives
111
  u=0.d0
112
  DO I=1,NCoord
113
     ! Given the arrays xgeom(1:NGeomI) and IntCoordI(1:NGeomI,Idx) of length 
114
     ! NGeomI, which tabulate a function
115
     ! (with the xgeom's in order), and given the array Coef(1:NGeomI,Idx), 
116
     ! which is the output from spline, and given a value of u,
117
     ! this routine returns a cubic-spline interpolated value v.
118
     ! and the derivative DerInt(Idx).
119
     call splintder(u,v,DerInt(I),NGeomI,xgeom(1),IntCoordI(1,I),Coef(1,I))
120
  END DO
121
  IntTangent(1,:)=DerInt
122

    
123
  IF (print.AND.(Dist.LE.1e20)) THEN
124
     WRITE(IOOUT,'(1X,I5)') Nat
125
     WRITE(IOOUT,*) "# Cartesian Coordinates for geom",1
126
     DO I=1,Nat
127
        If (Renum) THEN
128
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
129
                (XyzTmp2(Order(I),J),J=1,3)
130
        ELSE
131
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
132
                (XyzTmp2(I,J),J=1,3)
133
        END IF
134
     END DO
135
  END IF ! matches IF (print.AND.(Dist.LE.1e20)) THEN
136

    
137
  XyzTmp(:,1) = XyzGeomI(1,1,:) ! 1st index is geometry-index.
138
  XyzTmp(:,2) = XyzGeomI(1,2,:)
139
  XyzTmp(:,3) = XyzGeomI(1,3,:)
140

    
141
  s=0.d0
142
  IntCoord_k=IntCoordF(1,:)
143
  Xyz_k(:,1) = XyzGeomI(1,1,:) ! 1st index is geometry-index.
144
  Xyz_k(:,2) = XyzGeomI(1,2,:)
145
  Xyz_k(:,3) = XyzGeomI(1,3,:)
146
  IdxGeom=1
147
  XPrimRef=XPrimitive(1,:)
148
  XPrimitiveF(1,:)=XPrimitive(1,:)
149
  DO K=1,NMaxPtPath
150
     u=real(K)/NMaxPtPath*(NGeomI-1.)
151

    
152
     ! We generate the interpolated internal coordinates in v.
153
     ! Given the arrays Xgeom(1:NGeomI) (Xgeom(NGeomI): abscissa of all initial geometries)
154
     ! and IntCoordI(1:NGeomI,I) of length NGeomI, which tabulate a function (with the 
155
     ! Xgeom's in order), and given the array Coef(1:NGeomI,Idx), which is the output from 
156
     ! spline, and given a value of u, this routine returns a cubic-spline interpolated 
157
     ! value v and the derivative DerInt(I).
158

    
159
     ! this loop is to be confirmed:
160
     ! IntCoordI(NGeomI,3*Nat-6)
161
     DO I=1,NCoord
162
        call splintder(u,v,DerInt(I),NGeomI,Xgeom(1),IntCoordI(1,I),Coef(1,I))
163
        IntCoord_interpol(I)=v
164
     END DO
165
     IF(.NOT.FirstTimePathCreate) Then
166
       WRITE(*,*) "DBG Extrapol_baker Umat_local=UMatF"
167
        DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart()
168
           BTransInv_local(I,:) = BTransInvF(IdxGeom,I,:)
169
           UMat_local(:,I) = UMatF(IdxGeom,:,I)
170
        END DO
171
     END IF
172
     ! We convert it into Cartesian coordinates:
173
     if (debug) WRITE(*,*) "DBG Extrapol_baker, call ConvertBakerInt_car for k=",k
174
     Call ConvertBakerInternal_cart(IntCoord_k,IntCoord_interpol,Xyz_k(1,1), &
175
          Xyz_k(1,2),Xyz_k(1,3),XyzTMP2(1,1),XyzTMP2(1,2),XyzTMP2(1,3),XPrim,XPrimRef)
176
     XPrimRef=Xprim
177
     IF(.NOT.FirstTimePathCreate) Then
178
        DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart()
179
           BTransInvF(IdxGeom,I,:) = BTransInv_local(I,:)
180
        END DO
181
     END IF
182

    
183
     if (debug) THEN
184
        WRITE(*,*) "DBG Extrapol_baker, XyzTmp2 before RMSD"
185
           DO I=1,Nat
186
              IF (Renum) THEN
187
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
188
                      (XyzTmp2(Order(I),J),J=1,3)
189
              ELSE
190
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
191
                      (XyzTmp2(I,J),J=1,3)
192
              END IF
193
           END DO
194
        END IF
195
     
196

    
197
     call CalcRmsd(Nat,XyzTmp(1:Nat,1),XyzTmp(1:Nat,2),XyzTmp(1:Nat,3), &
198
    XyzTmp2(1:Nat,1),XyzTmp2(1:Nat,2),XyzTmp2(1:Nat,3),           &
199
          MRot,rmsd,.TRUE.,.TRUE.)
200

    
201

    
202
     if (debug) THEN
203
        WRITE(*,*) "DBG Extrapol_baker, XyzTmp2 after RMSD"
204
           DO I=1,Nat
205
              IF (Renum) THEN
206
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
207
                      (XyzTmp2(Order(I),J),J=1,3)
208
              ELSE
209
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
210
                      (XyzTmp2(I,J),J=1,3)
211
              END IF
212
           END DO
213
        END IF
214

    
215

    
216
     IntCoord_k=IntCoord_interpol
217
     Xyz_k(:,1)=XyzTMP2(:,1)
218
     Xyz_k(:,2)=XyzTMP2(:,2)
219
     Xyz_k(:,3)=XyzTMP2(:,3)
220

    
221
     ds=0.
222
     DO I=1,Nat
223
        DO J=1,3
224
           ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2
225
           XYZTmp(I,J)=XyzTMP2(I,J)
226
        END DO
227
     END DO
228

    
229
     s=s+sqrt(ds)
230

    
231
     IF (s>=dist) THEN
232
        if (debug) THEN
233
           WRITE(*,*) "DBG Extrapol_baker s,IdxGeom,dist",s,IdxGeom,dist
234
           WRITE(*,'(50(1X,F12.8))') IntCoord_interpol
235
           WRITE(*,*) "DBG Extrapol_baker Angles in deg ?"
236
           WRITE(*,'(50(1X,F12.8))') IntCoord_interpol*180./pi
237
        END IF
238
        s=s-dist
239
        IdxGeom=IdxGeom+1
240
        XprimitiveF(IdxGeom,:)=Xprim(:)
241
        UMatF(IdxGeom,:,:)=UMat_local(:,:)
242
        SGeom(IdxGeom)=s+IdxGeom*dist !SGeom(NGeomF)
243
        XgeomF(IdxGeom)=u
244
        XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
245

    
246
        ! IntCoordF(NGeomF,NCoord): Final Internal coordinates for number of final 
247
        ! geometries. NCoord is the number of coordinates (NCoord) of each geometry.
248
        IntCoordF(IdxGeom,:)=IntCoord_interpol(:)
249
        IntTangent(IdxGeom,:)=DerInt
250

    
251
        IF (print) THEN
252
           WRITE(IOOUT,'(1X,I5)') Nat
253
           WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K
254
           ! PFL 17/July/2006: only if we have more than 4 atoms.
255
           IF (Nat.GE.4) THEN
256
              Call  CalcRmsd(Nat,x0,y0,z0, &
257
                   xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), &
258
                   MRot,rmsd,.TRUE.,.TRUE.)
259
           END IF
260

    
261
           DO I=1,Nat
262
              IF (Renum) THEN
263
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
264
                      (XyzTmp2(Order(I),J),J=1,3)
265
              ELSE
266
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
267
                      (XyzTmp2(I,J),J=1,3)
268
              END IF
269
           END DO
270
        END IF !matches IF (print) THEN
271
     END IF ! matches IF (s>=dist) THEN
272
  END DO ! matches DO K=1,NMaxPtPath
273

    
274

    
275
  if (s>=0.9*dist) THEN
276
     s=s-dist
277
     IdxGeom=IdxGeom+1
278
     SGeom(IdxGeom)=s+IdxGeom*dist
279
     XgeomF(IdxGeom)=min(u,NGeomI-1.d0)
280
     XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
281
     !  XyzGeomF(IdxGeom,:,:)=XyzTmp2(:,:)
282

    
283
     IntCoordF(IdxGeom,:)=IntCoord_interpol(:)
284
     XprimitiveF(IdxGeom,:)=Xprim(:)
285
     UMatF(IdxGeom,:,:)=UMat_local(:,:)
286
     IntTangent(IdxGeom,:)=DerInt     
287

    
288
     if (print) THEN
289
        WRITE(IOOUT,'(1X,I5)') Nat
290
        WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K
291
        ! PFL 17/July/2006: only if we have more than 4 atoms.
292
        IF (Nat.GE.4) THEN
293
           Call  CalcRmsd(Nat,x0,y0,z0, &
294
                xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), &
295
                MRot,rmsd,.TRUE.,.TRUE.)
296
        END IF
297

    
298
        DO I=1,Nat
299
           IF (Renum) THEN
300
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
301
                   (XyzTmp2(Order(I),J),J=1,3)
302
           ELSE
303
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
304
                   (XyzTmp2(I,J),J=1,3)
305
           END IF
306
        END DO
307
     END IF ! matches if (print) THEN
308
  END IF ! matches if (s>=0.9*dist) THEN
309

    
310
  if (debug) WRITE(*,*) 's final =',s
311
   if (debug) THEN
312
      WRITE(*,*) "XPrimitiveF"
313
      DO I=1,NGeomF
314
        WRITE(*,'(1X,I5," : ",50(1X,F10.6))') I,XPrimitiveF(I,:)
315
     END DO
316
     END IF
317

    
318
  DEALLOCATE(XyzTmp,XyzTmp2,IntCoord_interpol,IntCoord_k,Xyz_k)
319

    
320
  if (printspline) CLOSE(IOTMP)
321
  if (debug) WRITE(*,*) "================= Extrapol_baker Over ====================="
322

    
323
END SUBROUTINE EXTRAPOL_BAKER