Statistiques
| Révision :

root / src / Extrapol_cart.f90 @ 6

Historique | Voir | Annoter | Télécharger (10,27 ko)

1
SUBROUTINE Extrapol_cart(iopt,s,dist,x0,y0,z0,xgeom,Coef)
2

    
3
  ! This subroutine constructs the path, and 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

    
11
  use Path_module
12
  use Io_module
13

    
14

    
15
  IMPLICIT NONE
16

    
17

    
18
  REAL(KREAL), INTENT(OUT) :: s
19
  ! X0(Nat),Y0(Nat),Z0(Nat): reference geometry.
20
  REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat)
21
  REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord)
22
! Iopt: Number of the cycles for the optimization
23
  INTEGER(KINT), INTENT(IN) :: Iopt
24
  INTEGER(KINT) :: IdxGeom, I, J, K, Idx,Iat, IGeom
25
! NSpline is the number of points along the interpolating path
26
  INTEGER(KINT) :: NSpline
27
! FileSpline: Filename to save the interpolating path coordinates
28
  CHARACTER(LCHARS) :: FileSpline,TmpChar
29
  REAL(KREAL) :: Rmsd,MRot(3,3), ds, u, v
30
  REAL(KREAL) :: a_val, d
31

    
32
  REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:) ! (Nat,3)
33
  REAL(KREAL), ALLOCATABLE :: DerXyz(:,:) ! Nat,3
34

    
35

    
36
  LOGICAL ::  debug, print, printspline
37
  LOGICAL, EXTERNAL :: valid
38

    
39
  !We will calculate the length of the path, in MW coordinates...
40
  ! this is done is a stupid way: we interpolate the zmatrix values,
41
  ! convert them into cartesian, weight the cartesian
42
  ! and calculate the evolution of the distance ! 
43
  ! We have to follow the same procedure for every geometry
44
  ! so even for the first one, we have to convert it from zmat
45
  ! to cartesian !
46

    
47
  debug=valid("pathcreate")
48
  print=valid("printgeom")
49

    
50
  printspline=(valid("printspline").AND.(dist<=1e30))
51

    
52
  if (debug) Call Header("Entering Extrapol_cart")
53

    
54
! We want 100 points along the interpolating path
55
  NSpline=int(NMaxPtPath/100)
56

    
57
  if (printspline) THEN
58
     WRITE(TmpChar,'(I5)') Iopt
59
     FileSpline=Trim(adjustL(PathName)) // '_spline.' // AdjustL(TRIM(TmpChar))
60
     OPEN(IOTMP,FILE=FileSpline)
61

    
62
  END IF
63

    
64

    
65
  ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),DerXyz(Nat,3))
66

    
67
! PFL 2011 June 22
68
! There was an alignment procedure there.
69
! It has been moved to PathCreate before the 
70
! computation of the Spline coefficient.
71

    
72
  XyzGeomF(1,:,:)=XyzGeomI(1,:,:)
73

    
74

    
75
  ! We initialize the first geometry
76

    
77
  XyzTmp=Reshape(XyzGeomI(1,:,:),(/Nat,3/),ORDER=(/2,1/))
78

    
79

    
80

    
81
  s=0.d0
82
  SGeom(1)=0.d0
83

    
84
  if (printspline) THEN
85
     u=0.d0
86
     DO Iat=1,Nat
87
        ! We generate the interpolated coordinates
88
        if (Linear) THEN
89
           call LinearInt(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat))
90
           call LinearInt(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat))
91
           call LinearInt(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat))
92

    
93
        ELSE
94
           call splintder(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat),Coef(1,3*Iat-2))
95
           call splintder(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat),Coef(1,3*Iat-1))
96
           call splintder(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat),Coef(1,3*Iat))
97
        END IF
98
     END DO
99

    
100
     WRITE(IOTMP,*) Nat
101
     WRITE(IOTMP,'(1X,A,1X,F15.6)') "Debug Spline - Coord=Cart,s=",s
102
     DO Iat=1,Nat
103
        WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)),    &
104
                   (XyzTmp2(Iat,1:3))
105
     END DO
106
  END IF
107

    
108
 IdxGeom=1
109

    
110
  DO K=1,NMaxPtPath
111
     u=real(K)/NMaxPtPath*(NGeomI-1.)
112

    
113
     DO Iat=1,Nat
114
        ! We generate the interpolated coordinates
115
        if (Linear) THEN
116
           call LinearInt(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat))
117
           call LinearInt(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat))
118
           call LinearInt(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat))
119

    
120
        ELSE
121
           call splintder(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat),Coef(1,3*Iat-2))
122
           call splintder(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat),Coef(1,3*Iat-1))
123
           call splintder(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat),Coef(1,3*Iat))
124
        END IF
125
     END DO
126

    
127

    
128
! PFL 2011 June 22: We now align on the previous one
129
! as we do for internal coord interpolation
130

    
131
! We align this geometry with the previous one
132

    
133
  ! PFL 17/July/2006: only if we have more than 4 atoms.
134
!  IF (Nat.GT.4) THEN
135
! PFL 24 Nov 2008 ->
136
! If we have frozen atoms we align only those ones.
137
! PFL 8 Feb 2011 ->
138
! I add a flag to see if we should align or not.
139
! For small systems, it might be better to let the user align himself
140
      IF (Align) THEN
141
         if (NFroz.GT.0) THEN
142
            Call AlignPartial(Nat,                     &
143
                 xyzTmp(1,1),xyzTmp(1,2),xyzTMP(1,3),       &
144
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
145
                 FrozAtoms,MRot)
146
         ELSE
147
            Call  CalcRmsd(Nat,                              &
148
                 xyzTmp(1,1),xyzTmp(1,2),xyzTMP(1,3),       &
149
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
150
                 MRot,rmsd,.TRUE.,.TRUE.)
151
         END IF
152
! <- PFL 24 Nov 2008
153
      END IF
154
! -> PFL 8 Feb 2011
155
!  END IF
156

    
157

    
158

    
159
     ds=0.
160
     DO I=1,Nat
161
        DO J=1,3
162
           ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2
163
           XYZTmp(I,J)=XyzTMP2(I,J)
164
        ENDDO
165
     ENDDO
166
     s=s+sqrt(ds)
167

    
168
     !         if (debug) WRITE(*,*) "Debug u,s,dist",u,s,dist
169

    
170
  if ((printspline).AND.(MOD(K,NSpline).EQ.0)) THEN
171
     WRITE(IOTMP,*) Nat
172
     WRITE(IOTMP,'(1X,A,1X,F15.6)') "Debug Spline - Coord=Cart,s=",s
173
     DO Iat=1,Nat
174
        WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)),    &
175
                   (XyzTmp2(Iat,1:3))
176
     END DO
177
  END IF
178

    
179

    
180
     if (s>=dist) THEN
181

    
182
        if (debug) THEN
183
           WRITE(*,*) "DBG Interpol_cart",s
184
           DO i=1,Nat
185
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),    &
186
                   (XyzTmp2(I,J),J=1,3)
187
           END DO
188
        END IF
189

    
190
        s=s-dist
191
        IdxGeom=IdxGeom+1
192
        SGeom(IdxGeom)=s+dist*(IdxGeom-1)
193

    
194
  ! We align this geometry with the original one
195
  ! PFL 17/July/2006: only if we have more than 4 atoms.
196
!  IF (Nat.GT.4) THEN
197
! PFL 24 Nov 2008 ->
198
! If we have frozen atoms we align only those ones.
199
! PFL 8 Feb 2011 ->
200
! I add a flag to see if we should align or not.
201
! For small systems, it might be better to let the user align himself
202
      IF (Align) THEN
203
         if (NFroz.GT.0) THEN
204
            Call AlignPartial(Nat,x0,y0,z0,                     &
205
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
206
                 FrozAtoms,MRot)
207
         ELSE
208
            Call  CalcRmsd(Nat, x0,y0,z0,                              &
209
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
210
                 MRot,rmsd,.TRUE.,.TRUE.)
211
         END IF
212
! <- PFL 24 Nov 2008
213
      END IF
214
! -> PFL 8 Feb 2011
215
!  END IF
216

    
217
        XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
218
        XyzTangent(IdxGeom,:)=Reshape(DerXyz(:,:),(/3*Nat/))
219

    
220
        if (print) THEN
221
           WRITE(IOOUT,'(1X,I5)') Nat
222
           WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K
223

    
224
           DO i=1,Nat
225
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),    &
226
                   (XyzTmp2(I,J),J=1,3)
227
           END DO
228

    
229
        END IF
230
     END IF  ! s>= dist
231
  ENDDO  ! K
232

    
233

    
234
  if (s>=0.9*dist) THEN
235
     s=s-dist
236
     XyzTmp2=Reshape(XyzGeomI(NGeomI,:,:),(/Nat,3/),ORDER=(/2,1/))
237

    
238
  if (printspline) THEN
239
     WRITE(IOTMP,*) Nat
240
     WRITE(IOTMP,*) "Debug Spline - Coord=Cart,s=",s
241
     DO Iat=1,Nat
242
        WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)),    &
243
                   (XyzTmp2(Iat,1:3))
244
     END DO
245
  END IF
246

    
247

    
248
  ! We align this geometry with the original one
249
  ! PFL 17/July/2006: only if we have more than 4 atoms.
250
!  IF (Nat.GT.4) THEN
251
! PFL 24 Nov 2008 ->
252
! If we have frozen atoms we align only those ones.
253
! PFL 8 Feb 2011 ->
254
! I add a flag to see if we should align or not.
255
! For small systems, it might be better to let the user align himself
256
      IF (Align) THEN
257
         if (NFroz.GT.0) THEN
258
            Call AlignPartial(Nat,x0,y0,z0,                     &
259
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
260
                 FrozAtoms,MRot)
261
         ELSE
262
            Call  CalcRmsd(Nat, x0,y0,z0,                              &
263
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
264
                 MRot,rmsd,.TRUE.,.TRUE.)
265
         END IF
266
! <- PFL 24 Nov 2008
267
      END IF
268
! -> PFL 8 Feb 2011
269
!  END IF
270

    
271
     IdxGeom=IdxGeom+1
272
     SGeom(IdxGeom)=s+dist*(IdxGeom-1)
273

    
274
    IF (IdxGeom.GT.NGeomF) THEN
275
        WRITE(IOOUT,*) "!!! ERROR in Extrapol_cart !!!!"
276
        WRITE(IOOUT,*) "Too many structures. Increase NMaxPath"
277
        WRITE(*,*) "** PathCreate ***"
278
        WRITE(*,*) "Distribution of points along the path is wrong."
279
        WRITE(*,*) "Increase value of NMaxPtPath in the input file"
280
        WRITE(*,*) "Present value is:", NMaxPtPath
281
        STOP
282
     END IF
283

    
284

    
285
  ! We align this geometry with the original one
286
  ! PFL 17/July/2006: only if we have more than 4 atoms.
287
!  IF (Nat.GT.4) THEN
288
! PFL 24 Nov 2008 ->
289
! If we have frozen atoms we align only those ones.
290
! PFL 8 Feb 2011 ->
291
! I add a flag to see if we should align or not.
292
! For small systems, it might be better to let the user align himself
293
      IF (Align) THEN
294
         if (NFroz.GT.0) THEN
295
            Call AlignPartial(Nat,x0,y0,z0,                     &
296
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
297
                 FrozAtoms,MRot)
298
         ELSE
299
            Call  CalcRmsd(Nat, x0,y0,z0,                              &
300
                 xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
301
                 MRot,rmsd,.TRUE.,.TRUE.)
302
         END IF
303
! <- PFL 24 Nov 2008
304
      END IF
305
! -> PFL 8 Feb 2011
306
!  END IF
307

    
308
     XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
309
     XyzTangent(IdxGeom,:)=Reshape(DerXyz(:,:),(/3*Nat/))
310

    
311
     if (print) THEN
312
        WRITE(IOOUT,'(1X,I5)') Nat
313
        WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K
314

    
315
        DO i=1,Nat
316
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),     &
317
                (XyzTmp2(I,J),J=1,3)
318
        END DO
319
     END IF
320
  END IF
321

    
322
  DEALLOCATE(XyzTmp,XyzTmp2)
323

    
324
  if (debug) WRITE(*,*) 's final =',s
325

    
326
  if (printspline) CLOSE(IOTMP)
327

    
328
  if (debug) Call Header("Extrapol_cart over")
329

    
330
END SUBROUTINE EXTRAPOL_CART