root / src / Extrapol_cart.f90 @ 12
Historique | Voir | Annoter | Télécharger (12,03 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 |
!---------------------------------------------------------------------- |
12 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
13 |
! Centre National de la Recherche Scientifique, |
14 |
! Université Claude Bernard Lyon 1. All rights reserved. |
15 |
! |
16 |
! This work is registered with the Agency for the Protection of Programs |
17 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
18 |
! |
19 |
! Authors: P. Fleurat-Lessard, P. Dayal |
20 |
! Contact: optnpath@gmail.com |
21 |
! |
22 |
! This file is part of "Opt'n Path". |
23 |
! |
24 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
25 |
! it under the terms of the GNU Affero General Public License as |
26 |
! published by the Free Software Foundation, either version 3 of the License, |
27 |
! or (at your option) any later version. |
28 |
! |
29 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
30 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
31 |
! |
32 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
33 |
! GNU Affero General Public License for more details. |
34 |
! |
35 |
! You should have received a copy of the GNU Affero General Public License |
36 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
37 |
! |
38 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
39 |
! for commercial licensing opportunities. |
40 |
!---------------------------------------------------------------------- |
41 |
|
42 |
use Path_module |
43 |
use Io_module |
44 |
|
45 |
|
46 |
IMPLICIT NONE |
47 |
|
48 |
|
49 |
REAL(KREAL), INTENT(OUT) :: s |
50 |
! X0(Nat),Y0(Nat),Z0(Nat): reference geometry. |
51 |
REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat) |
52 |
REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord) |
53 |
! Iopt: Number of the cycles for the optimization |
54 |
INTEGER(KINT), INTENT(IN) :: Iopt |
55 |
INTEGER(KINT) :: IdxGeom, I, J, K, Iat |
56 |
! NSpline is the number of points along the interpolating path |
57 |
INTEGER(KINT) :: NSpline |
58 |
! FileSpline: Filename to save the interpolating path coordinates |
59 |
CHARACTER(LCHARS) :: FileSpline,TmpChar |
60 |
REAL(KREAL) :: Rmsd, MRot(3, 3), ds, u |
61 |
|
62 |
REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:) ! (Nat,3) |
63 |
REAL(KREAL), ALLOCATABLE :: DerXyz(:,:) ! Nat,3 |
64 |
|
65 |
|
66 |
LOGICAL :: debug, print, printspline |
67 |
LOGICAL, EXTERNAL :: valid |
68 |
|
69 |
!We will calculate the length of the path, in MW coordinates... |
70 |
! this is done is a stupid way: we interpolate the zmatrix values, |
71 |
! convert them into cartesian, weight the cartesian |
72 |
! and calculate the evolution of the distance ! |
73 |
! We have to follow the same procedure for every geometry |
74 |
! so even for the first one, we have to convert it from zmat |
75 |
! to cartesian ! |
76 |
|
77 |
debug=valid("pathcreate") |
78 |
print=valid("printgeom") |
79 |
|
80 |
printspline=(valid("printspline").AND.(dist<=1e30)) |
81 |
|
82 |
if (debug) Call Header("Entering Extrapol_cart") |
83 |
|
84 |
! We want 100 points along the interpolating path |
85 |
NSpline=int(NMaxPtPath/100) |
86 |
|
87 |
if (printspline) THEN |
88 |
WRITE(TmpChar,'(I5)') Iopt |
89 |
FileSpline=Trim(adjustL(PathName)) // '_spline.' // AdjustL(TRIM(TmpChar)) |
90 |
OPEN(IOTMP,FILE=FileSpline) |
91 |
|
92 |
END IF |
93 |
|
94 |
|
95 |
ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),DerXyz(Nat,3)) |
96 |
|
97 |
! PFL 2011 June 22 |
98 |
! There was an alignment procedure there. |
99 |
! It has been moved to PathCreate before the |
100 |
! computation of the Spline coefficient. |
101 |
|
102 |
if (debug) THEN |
103 |
WRITE(*,*) "Extrapol_cart- L72 - geometries " |
104 |
DO I=1,NGeomI |
105 |
WRITE(*,*) "Geom ",I |
106 |
DO J=1,Nat |
107 |
If (renum) THEN |
108 |
Iat=Order(J) |
109 |
WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(J)),XyzGeomI(I,1:3,Iat) |
110 |
ELSE |
111 |
Iat=OrderInv(J) |
112 |
WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),XyzGeomI(I,1:3,J) |
113 |
END IF |
114 |
END DO |
115 |
END DO |
116 |
END IF |
117 |
|
118 |
|
119 |
XyzGeomF(1,:,:)=XyzGeomI(1,:,:) |
120 |
|
121 |
|
122 |
! We initialize the first geometry |
123 |
|
124 |
XyzTmp=Reshape(XyzGeomI(1,:,:),(/Nat,3/),ORDER=(/2,1/)) |
125 |
|
126 |
|
127 |
|
128 |
s=0.d0 |
129 |
SGeom(1)=0.d0 |
130 |
|
131 |
if (printspline) THEN |
132 |
u=0.d0 |
133 |
DO Iat=1,Nat |
134 |
! We generate the interpolated coordinates |
135 |
if (Linear) THEN |
136 |
call LinearInt(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat)) |
137 |
call LinearInt(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat)) |
138 |
call LinearInt(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat)) |
139 |
|
140 |
ELSE |
141 |
call splintder(u,XyzTmp2(Iat,1),DerXyz(Iat,1),NGeomI,xgeom(1),XyzGeomI(1,1,Iat),Coef(1,3*Iat-2)) |
142 |
call splintder(u,XyzTmp2(Iat,2),DerXyz(Iat,2),NGeomI,xgeom(1),XyzGeomI(1,2,Iat),Coef(1,3*Iat-1)) |
143 |
call splintder(u,XyzTmp2(Iat,3),DerXyz(Iat,3),NGeomI,xgeom(1),XyzGeomI(1,3,Iat),Coef(1,3*Iat)) |
144 |
END IF |
145 |
END DO |
146 |
|
147 |
WRITE(IOTMP,*) Nat |
148 |
WRITE(IOTMP,'(1X,A,1X,F15.6)') "Debug Spline - Coord=Cart,s=",s |
149 |
DO Iat=1,Nat |
150 |
WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)), & |
151 |
(XyzTmp2(Iat,1:3)) |
152 |
END DO |
153 |
END IF |
154 |
|
155 |
IdxGeom=1 |
156 |
|
157 |
DO K=1,NMaxPtPath |
158 |
u=real(K)/NMaxPtPath*(NGeomI-1.) |
159 |
|
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 |
|
175 |
! PFL 2011 June 22: We now align on the previous one |
176 |
! as we do for internal coord interpolation |
177 |
|
178 |
! We align this geometry with the previous one |
179 |
|
180 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
181 |
! IF (Nat.GT.4) THEN |
182 |
! PFL 24 Nov 2008 -> |
183 |
! If we have frozen atoms we align only those ones. |
184 |
! PFL 8 Feb 2011 -> |
185 |
! I add a flag to see if we should align or not. |
186 |
! For small systems, it might be better to let the user align himself |
187 |
IF (Align) THEN |
188 |
if (NFroz.GT.0) THEN |
189 |
Call AlignPartial(Nat, & |
190 |
xyzTmp(1,1),xyzTmp(1,2),xyzTMP(1,3), & |
191 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
192 |
FrozAtoms,MRot) |
193 |
ELSE |
194 |
Call CalcRmsd(Nat, & |
195 |
xyzTmp(1,1),xyzTmp(1,2),xyzTMP(1,3), & |
196 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
197 |
MRot,rmsd,.TRUE.,.TRUE.) |
198 |
END IF |
199 |
! <- PFL 24 Nov 2008 |
200 |
END IF |
201 |
! -> PFL 8 Feb 2011 |
202 |
! END IF |
203 |
|
204 |
|
205 |
|
206 |
ds=0. |
207 |
DO I=1,Nat |
208 |
DO J=1,3 |
209 |
ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2 |
210 |
XYZTmp(I,J)=XyzTMP2(I,J) |
211 |
ENDDO |
212 |
ENDDO |
213 |
s=s+sqrt(ds) |
214 |
|
215 |
! if (debug) WRITE(*,*) "Debug u,s,dist",u,s,dist |
216 |
|
217 |
if ((printspline).AND.(MOD(K,NSpline).EQ.0)) THEN |
218 |
WRITE(IOTMP,*) Nat |
219 |
WRITE(IOTMP,'(1X,A,1X,F15.6)') "Debug Spline - Coord=Cart,s=",s |
220 |
DO Iat=1,Nat |
221 |
WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)), & |
222 |
(XyzTmp2(Iat,1:3)) |
223 |
END DO |
224 |
END IF |
225 |
|
226 |
|
227 |
if (s>=dist) THEN |
228 |
|
229 |
if (debug) THEN |
230 |
WRITE(*,*) "DBG Interpol_cart",s |
231 |
DO i=1,Nat |
232 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
233 |
(XyzTmp2(I,J),J=1,3) |
234 |
END DO |
235 |
END IF |
236 |
|
237 |
s=s-dist |
238 |
IdxGeom=IdxGeom+1 |
239 |
SGeom(IdxGeom)=s+dist*(IdxGeom-1) |
240 |
|
241 |
! We align this geometry with the original one |
242 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
243 |
! IF (Nat.GT.4) THEN |
244 |
! PFL 24 Nov 2008 -> |
245 |
! If we have frozen atoms we align only those ones. |
246 |
! PFL 8 Feb 2011 -> |
247 |
! I add a flag to see if we should align or not. |
248 |
! For small systems, it might be better to let the user align himself |
249 |
IF (Align) THEN |
250 |
if (NFroz.GT.0) THEN |
251 |
Call AlignPartial(Nat,x0,y0,z0, & |
252 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
253 |
FrozAtoms,MRot) |
254 |
ELSE |
255 |
Call CalcRmsd(Nat, x0,y0,z0, & |
256 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
257 |
MRot,rmsd,.TRUE.,.TRUE.) |
258 |
END IF |
259 |
! <- PFL 24 Nov 2008 |
260 |
END IF |
261 |
! -> PFL 8 Feb 2011 |
262 |
! END IF |
263 |
|
264 |
XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
265 |
XyzTangent(IdxGeom,:)=Reshape(DerXyz(:,:),(/3*Nat/)) |
266 |
|
267 |
if (print) THEN |
268 |
WRITE(IOOUT,'(1X,I5)') Nat |
269 |
WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K |
270 |
|
271 |
DO i=1,Nat |
272 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
273 |
(XyzTmp2(I,J),J=1,3) |
274 |
END DO |
275 |
|
276 |
END IF |
277 |
END IF ! s>= dist |
278 |
ENDDO ! K |
279 |
|
280 |
|
281 |
if (s>=0.9*dist) THEN |
282 |
s=s-dist |
283 |
XyzTmp2=Reshape(XyzGeomI(NGeomI,:,:),(/Nat,3/),ORDER=(/2,1/)) |
284 |
|
285 |
if (printspline) THEN |
286 |
WRITE(IOTMP,*) Nat |
287 |
WRITE(IOTMP,*) "Debug Spline - Coord=Cart,s=",s |
288 |
DO Iat=1,Nat |
289 |
WRITE(IOTMP,'(1X,A2,3(1X,F15.6))') Nom(Atome(Iat)), & |
290 |
(XyzTmp2(Iat,1:3)) |
291 |
END DO |
292 |
END IF |
293 |
|
294 |
|
295 |
! We align this geometry with the original one |
296 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
297 |
! IF (Nat.GT.4) THEN |
298 |
! PFL 24 Nov 2008 -> |
299 |
! If we have frozen atoms we align only those ones. |
300 |
! PFL 8 Feb 2011 -> |
301 |
! I add a flag to see if we should align or not. |
302 |
! For small systems, it might be better to let the user align himself |
303 |
IF (Align) THEN |
304 |
if (NFroz.GT.0) THEN |
305 |
Call AlignPartial(Nat,x0,y0,z0, & |
306 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
307 |
FrozAtoms,MRot) |
308 |
ELSE |
309 |
Call CalcRmsd(Nat, x0,y0,z0, & |
310 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
311 |
MRot,rmsd,.TRUE.,.TRUE.) |
312 |
END IF |
313 |
! <- PFL 24 Nov 2008 |
314 |
END IF |
315 |
! -> PFL 8 Feb 2011 |
316 |
! END IF |
317 |
|
318 |
IdxGeom=IdxGeom+1 |
319 |
SGeom(IdxGeom)=s+dist*(IdxGeom-1) |
320 |
|
321 |
IF (IdxGeom.GT.NGeomF) THEN |
322 |
WRITE(IOOUT,*) "!!! ERROR in Extrapol_cart !!!!" |
323 |
WRITE(IOOUT,*) "Too many structures. Increase NMaxPath" |
324 |
WRITE(*,*) "** PathCreate ***" |
325 |
WRITE(*,*) "Distribution of points along the path is wrong." |
326 |
WRITE(*,*) "Increase value of NMaxPtPath in the input file" |
327 |
WRITE(*,*) "Present value is:", NMaxPtPath |
328 |
STOP |
329 |
END IF |
330 |
|
331 |
|
332 |
! We align this geometry with the original one |
333 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
334 |
! IF (Nat.GT.4) THEN |
335 |
! PFL 24 Nov 2008 -> |
336 |
! If we have frozen atoms we align only those ones. |
337 |
! PFL 8 Feb 2011 -> |
338 |
! I add a flag to see if we should align or not. |
339 |
! For small systems, it might be better to let the user align himself |
340 |
IF (Align) THEN |
341 |
if (NFroz.GT.0) THEN |
342 |
Call AlignPartial(Nat,x0,y0,z0, & |
343 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
344 |
FrozAtoms,MRot) |
345 |
ELSE |
346 |
Call CalcRmsd(Nat, x0,y0,z0, & |
347 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
348 |
MRot,rmsd,.TRUE.,.TRUE.) |
349 |
END IF |
350 |
! <- PFL 24 Nov 2008 |
351 |
END IF |
352 |
! -> PFL 8 Feb 2011 |
353 |
! END IF |
354 |
|
355 |
XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
356 |
XyzTangent(IdxGeom,:)=Reshape(DerXyz(:,:),(/3*Nat/)) |
357 |
|
358 |
if (print) THEN |
359 |
WRITE(IOOUT,'(1X,I5)') Nat |
360 |
WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K |
361 |
|
362 |
DO i=1,Nat |
363 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
364 |
(XyzTmp2(I,J),J=1,3) |
365 |
END DO |
366 |
END IF |
367 |
END IF |
368 |
|
369 |
DEALLOCATE(XyzTmp,XyzTmp2) |
370 |
|
371 |
if (debug) WRITE(*,*) 's final =',s |
372 |
|
373 |
if (printspline) CLOSE(IOTMP) |
374 |
|
375 |
if (debug) Call Header("Extrapol_cart over") |
376 |
|
377 |
END SUBROUTINE EXTRAPOL_CART |