root / src / Extrapol_cart.f90 @ 2
Historique | Voir | Annoter | Télécharger (12,42 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 |
! XyzTmp2=Reshape(XyzGeomI(1,:,:),(/Nat,3/),ORDER=(/2,1/)) |
68 |
|
69 |
if (debug) THEN |
70 |
WRITE(*,*) "DBG Extrapol_cart Initial geometries" |
71 |
DO IGeom=1,NGeomI |
72 |
WRITE(*,*) 'XyzGeomI, IGeom=',IGeom |
73 |
DO I=1,Nat |
74 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
75 |
(XyzGeomI(IGeom,J,I),J=1,3) |
76 |
END DO |
77 |
END DO |
78 |
END IF |
79 |
|
80 |
|
81 |
! In order to mesure only the relevant distance between two points |
82 |
! we align all geometries on the original one |
83 |
|
84 |
DO IGeom=1,NGeomI |
85 |
|
86 |
XyzTmp2=Reshape(XyzGeomI(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)) |
87 |
! We align this geometry with the original one |
88 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
89 |
! IF (Nat.GT.4) THEN |
90 |
! PFL 24 Nov 2008 -> |
91 |
! If we have frozen atoms we align only those ones. |
92 |
! PFL 8 Feb 2011 -> |
93 |
! I add a flag to see if we should align or not. |
94 |
! For small systems, it might be better to let the user align himself |
95 |
IF (Align) THEN |
96 |
if (NFroz.GT.0) THEN |
97 |
Call AlignPartial(Nat,x0,y0,z0, & |
98 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
99 |
FrozAtoms,MRot) |
100 |
ELSE |
101 |
Call CalcRmsd(Nat, x0,y0,z0, & |
102 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
103 |
MRot,rmsd,.TRUE.,.TRUE.) |
104 |
END IF |
105 |
! <- PFL 24 Nov 2008 |
106 |
END IF |
107 |
! -> PFL 8 Feb 2011 |
108 |
! END IF |
109 |
|
110 |
XyzGeomI(IGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
111 |
END DO |
112 |
|
113 |
if (print) THEN |
114 |
WRITE(*,*) "Aligned geometries" |
115 |
DO J=1, NGeomI |
116 |
WRITE(IOOUT,*) Nat |
117 |
WRITE(IOOUT,*) " Aligned geometry ",J,"/",NGeomI |
118 |
DO i=1,Nat |
119 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
120 |
XyzGeomI(J,1:3,I) |
121 |
END DO |
122 |
END DO |
123 |
END IF |
124 |
|
125 |
XyzGeomF(1,:,:)=XyzGeomI(1,:,:) |
126 |
|
127 |
|
128 |
! We initialize the first geometry |
129 |
|
130 |
XyzTmp=Reshape(XyzGeomI(1,:,:),(/Nat,3/),ORDER=(/2,1/)) |
131 |
|
132 |
! We align this geometry with the original one |
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,x0,y0,z0, & |
143 |
xyzTmp(1,1),xyzTmp(1,2),xyzTMP(1,3), & |
144 |
FrozAtoms,MRot) |
145 |
ELSE |
146 |
Call CalcRmsd(Nat, x0,y0,z0, & |
147 |
xyzTmp(1,1),xyzTmp(1,2),xyzTMP(1,3), & |
148 |
MRot,rmsd,.TRUE.,.TRUE.) |
149 |
END IF |
150 |
! <- PFL 24 Nov 2008 |
151 |
END IF |
152 |
! -> PFL 8 Feb 2011 |
153 |
! END IF |
154 |
|
155 |
|
156 |
|
157 |
s=0.d0 |
158 |
if (printspline) THEN |
159 |
u=0.d0 |
160 |
DO Iat=1,Nat |
161 |
! We generate the interpolated coordinates |
162 |
if (Linear) THEN |
163 |
call LinearInt(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat)) |
164 |
call LinearInt(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat)) |
165 |
call LinearInt(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat)) |
166 |
|
167 |
ELSE |
168 |
call splintder(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat),Coef(1,3*Iat-2)) |
169 |
call splintder(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat),Coef(1,3*Iat-1)) |
170 |
call splintder(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat),Coef(1,3*Iat)) |
171 |
END IF |
172 |
END DO |
173 |
|
174 |
WRITE(IOTMP,*) Nat |
175 |
WRITE(IOTMP,'(1X,A,1X,F15.6)') "Debug Spline - Coord=Cart,s=",s |
176 |
DO Iat=1,Nat |
177 |
WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)), & |
178 |
(XyzTmp2(Iat,1:3)) |
179 |
END DO |
180 |
END IF |
181 |
|
182 |
IdxGeom=1 |
183 |
|
184 |
DO K=1,NMaxPtPath |
185 |
u=real(K)/NMaxPtPath*(NGeomI-1.) |
186 |
|
187 |
DO Iat=1,Nat |
188 |
! We generate the interpolated coordinates |
189 |
if (Linear) THEN |
190 |
call LinearInt(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat)) |
191 |
call LinearInt(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat)) |
192 |
call LinearInt(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat)) |
193 |
|
194 |
ELSE |
195 |
call splintder(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat),Coef(1,3*Iat-2)) |
196 |
call splintder(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat),Coef(1,3*Iat-1)) |
197 |
call splintder(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat),Coef(1,3*Iat)) |
198 |
END IF |
199 |
END DO |
200 |
|
201 |
|
202 |
! We align this geometry with the original one |
203 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
204 |
! IF (Nat.GT.4) THEN |
205 |
! PFL 24 Nov 2008 -> |
206 |
! If we have frozen atoms we align only those ones. |
207 |
! PFL 8 Feb 2011 -> |
208 |
! I add a flag to see if we should align or not. |
209 |
! For small systems, it might be better to let the user align himself |
210 |
IF (Align) THEN |
211 |
if (NFroz.GT.0) THEN |
212 |
Call AlignPartial(Nat,x0,y0,z0, & |
213 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
214 |
FrozAtoms,MRot) |
215 |
ELSE |
216 |
Call CalcRmsd(Nat, x0,y0,z0, & |
217 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
218 |
MRot,rmsd,.TRUE.,.TRUE.) |
219 |
END IF |
220 |
! <- PFL 24 Nov 2008 |
221 |
END IF |
222 |
! -> PFL 8 Feb 2011 |
223 |
! END IF |
224 |
|
225 |
|
226 |
|
227 |
ds=0. |
228 |
DO I=1,Nat |
229 |
DO J=1,3 |
230 |
ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2 |
231 |
XYZTmp(I,J)=XyzTMP2(I,J) |
232 |
ENDDO |
233 |
ENDDO |
234 |
s=s+sqrt(ds) |
235 |
|
236 |
! if (debug) WRITE(*,*) "Debug u,s,dist",u,s,dist |
237 |
|
238 |
if ((printspline).AND.(MOD(K,NSpline).EQ.0)) THEN |
239 |
WRITE(IOTMP,*) Nat |
240 |
WRITE(IOTMP,'(1X,A,1X,F15.6)') "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 |
if (s>=dist) THEN |
249 |
|
250 |
if (debug) THEN |
251 |
WRITE(*,*) "DBG Interpol_cart",s |
252 |
DO i=1,Nat |
253 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
254 |
(XyzTmp2(I,J),J=1,3) |
255 |
END DO |
256 |
END IF |
257 |
|
258 |
s=s-dist |
259 |
IdxGeom=IdxGeom+1 |
260 |
|
261 |
! We align this geometry with the original one |
262 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
263 |
! IF (Nat.GT.4) THEN |
264 |
! PFL 24 Nov 2008 -> |
265 |
! If we have frozen atoms we align only those ones. |
266 |
! PFL 8 Feb 2011 -> |
267 |
! I add a flag to see if we should align or not. |
268 |
! For small systems, it might be better to let the user align himself |
269 |
IF (Align) THEN |
270 |
if (NFroz.GT.0) THEN |
271 |
Call AlignPartial(Nat,x0,y0,z0, & |
272 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
273 |
FrozAtoms,MRot) |
274 |
ELSE |
275 |
Call CalcRmsd(Nat, x0,y0,z0, & |
276 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
277 |
MRot,rmsd,.TRUE.,.TRUE.) |
278 |
END IF |
279 |
! <- PFL 24 Nov 2008 |
280 |
END IF |
281 |
! -> PFL 8 Feb 2011 |
282 |
! END IF |
283 |
|
284 |
XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
285 |
XyzTangent(IdxGeom,:)=Reshape(DerXyz(:,:),(/3*Nat/)) |
286 |
|
287 |
if (print) THEN |
288 |
WRITE(IOOUT,'(1X,I5)') Nat |
289 |
WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K |
290 |
|
291 |
DO i=1,Nat |
292 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
293 |
(XyzTmp2(I,J),J=1,3) |
294 |
END DO |
295 |
|
296 |
END IF |
297 |
END IF ! s>= dist |
298 |
ENDDO ! K |
299 |
|
300 |
|
301 |
if (s>=0.9*dist) THEN |
302 |
s=s-dist |
303 |
XyzTmp2=Reshape(XyzGeomI(NGeomI,:,:),(/Nat,3/),ORDER=(/2,1/)) |
304 |
|
305 |
if (printspline) THEN |
306 |
WRITE(IOTMP,*) Nat |
307 |
WRITE(IOTMP,*) "Debug Spline - Coord=Cart,s=",s |
308 |
DO Iat=1,Nat |
309 |
WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)), & |
310 |
(XyzTmp2(Iat,1:3)) |
311 |
END DO |
312 |
END IF |
313 |
|
314 |
|
315 |
! We align this geometry with the original one |
316 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
317 |
! IF (Nat.GT.4) THEN |
318 |
! PFL 24 Nov 2008 -> |
319 |
! If we have frozen atoms we align only those ones. |
320 |
! PFL 8 Feb 2011 -> |
321 |
! I add a flag to see if we should align or not. |
322 |
! For small systems, it might be better to let the user align himself |
323 |
IF (Align) THEN |
324 |
if (NFroz.GT.0) THEN |
325 |
Call AlignPartial(Nat,x0,y0,z0, & |
326 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
327 |
FrozAtoms,MRot) |
328 |
ELSE |
329 |
Call CalcRmsd(Nat, x0,y0,z0, & |
330 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
331 |
MRot,rmsd,.TRUE.,.TRUE.) |
332 |
END IF |
333 |
! <- PFL 24 Nov 2008 |
334 |
END IF |
335 |
! -> PFL 8 Feb 2011 |
336 |
! END IF |
337 |
|
338 |
IdxGeom=IdxGeom+1 |
339 |
|
340 |
IF (IdxGeom.GT.NGeomF) THEN |
341 |
WRITE(IOOUT,*) "!!! ERROR in Extrapol_cart !!!!" |
342 |
WRITE(IOOUT,*) "Too many structures. Increase NMaxPath" |
343 |
WRITE(*,*) "** PathCreate ***" |
344 |
WRITE(*,*) "Distribution of points along the path is wrong." |
345 |
WRITE(*,*) "Increase value of NMaxPtPath in the input file" |
346 |
WRITE(*,*) "Present value is:", NMaxPtPath |
347 |
STOP |
348 |
END IF |
349 |
|
350 |
|
351 |
! We align this geometry with the original one |
352 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
353 |
! IF (Nat.GT.4) THEN |
354 |
! PFL 24 Nov 2008 -> |
355 |
! If we have frozen atoms we align only those ones. |
356 |
! PFL 8 Feb 2011 -> |
357 |
! I add a flag to see if we should align or not. |
358 |
! For small systems, it might be better to let the user align himself |
359 |
IF (Align) THEN |
360 |
if (NFroz.GT.0) THEN |
361 |
Call AlignPartial(Nat,x0,y0,z0, & |
362 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
363 |
FrozAtoms,MRot) |
364 |
ELSE |
365 |
Call CalcRmsd(Nat, x0,y0,z0, & |
366 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
367 |
MRot,rmsd,.TRUE.,.TRUE.) |
368 |
END IF |
369 |
! <- PFL 24 Nov 2008 |
370 |
END IF |
371 |
! -> PFL 8 Feb 2011 |
372 |
! END IF |
373 |
|
374 |
XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
375 |
XyzTangent(IdxGeom,:)=Reshape(DerXyz(:,:),(/3*Nat/)) |
376 |
|
377 |
if (print) THEN |
378 |
WRITE(IOOUT,'(1X,I5)') Nat |
379 |
WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K |
380 |
|
381 |
DO i=1,Nat |
382 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
383 |
(XyzTmp2(I,J),J=1,3) |
384 |
END DO |
385 |
END IF |
386 |
END IF |
387 |
|
388 |
DEALLOCATE(XyzTmp,XyzTmp2) |
389 |
|
390 |
if (debug) WRITE(*,*) 's final =',s |
391 |
|
392 |
if (printspline) CLOSE(IOTMP) |
393 |
|
394 |
if (debug) Call Header("Extrapol_cart over") |
395 |
|
396 |
END SUBROUTINE EXTRAPOL_CART |