root / src / Extrapol_int.f90
Historique | Voir | Annoter | Télécharger (17,97 ko)
1 |
SUBROUTINE Extrapol_int(iopt,s,dist,x0,y0,z0,xgeom,Coef,XgeomF) |
---|---|
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 |
! Default value of FRot=.TRUE. |
12 |
! Default value of NMaxPtPath = 1000 |
13 |
! IntCoordI(:,:) ! (NGeomI,3*Nat-6) |
14 |
! XyzGeomF(:,:,:) ! (NGeomF,3,Nat) |
15 |
! Default value of FAlign=.TRUE. |
16 |
|
17 |
!---------------------------------------------------------------------- |
18 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
19 |
! Centre National de la Recherche Scientifique, |
20 |
! Université Claude Bernard Lyon 1. All rights reserved. |
21 |
! |
22 |
! This work is registered with the Agency for the Protection of Programs |
23 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
24 |
! |
25 |
! Authors: P. Fleurat-Lessard, P. Dayal |
26 |
! Contact: optnpath@gmail.com |
27 |
! |
28 |
! This file is part of "Opt'n Path". |
29 |
! |
30 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
31 |
! it under the terms of the GNU Affero General Public License as |
32 |
! published by the Free Software Foundation, either version 3 of the License, |
33 |
! or (at your option) any later version. |
34 |
! |
35 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
36 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
37 |
! |
38 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
39 |
! GNU Affero General Public License for more details. |
40 |
! |
41 |
! You should have received a copy of the GNU Affero General Public License |
42 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
43 |
! |
44 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
45 |
! for commercial licensing opportunities. |
46 |
!---------------------------------------------------------------------- |
47 |
|
48 |
|
49 |
use Path_module, only : NMaxPtPath, IntCoordI, Pi, IndZmat, XyzGeomF, & |
50 |
IntCoordF, IntTangent, Renum, Nom, Order, MassAt, SGeom, & |
51 |
Atome, Nat, NGeomI, NCoord, NGeomF, OrderInv,NFroz,FrozAtoms,Align |
52 |
! IndZmat(Nat,5) |
53 |
|
54 |
use Io_module |
55 |
|
56 |
|
57 |
IMPLICIT NONE |
58 |
|
59 |
|
60 |
REAL(KREAL), INTENT(OUT) :: s |
61 |
! X0(Nat),Y0(Nat),Z0(Nat): reference geometry. |
62 |
REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat) |
63 |
REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord) |
64 |
! Iopt: Number of the cycles for the optimization |
65 |
INTEGER(KINT), INTENT(IN) :: Iopt |
66 |
REAL(KREAL), INTENT(OUT) :: XGeomF(NGeomF) |
67 |
|
68 |
INTEGER(KINT) :: IdxGeom, I, J, K, Idx |
69 |
REAL(KREAL) :: Rmsd,MRot(3,3), ds, u, v |
70 |
REAL(KREAL) :: a_val, d |
71 |
|
72 |
REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:) ! (Nat,3) |
73 |
REAL(KREAL), ALLOCATABLE :: ValZmat(:,:),DerInt(:) ! (Nat,3) |
74 |
|
75 |
|
76 |
LOGICAL :: debug, print,printspline |
77 |
LOGICAL, EXTERNAL :: valid |
78 |
|
79 |
INTEGER(KINT) :: NSpline |
80 |
CHARACTER(LCHARS) :: FileSpline,TmpChar |
81 |
|
82 |
|
83 |
! LOGICAL :: FAlign=.FALSE., FRot=.FALSE. |
84 |
|
85 |
! We will calculate the length of the path, in MW coordinates... |
86 |
! this is done is a stupid way: we interpolate the zmatrix values, |
87 |
! convert them into cartesian, weight the cartesian |
88 |
! and calculate the evolution of the distance ! |
89 |
! We have to follow the same procedure for every geometry |
90 |
! so even for the first one, we have to convert it from zmat |
91 |
! to cartesian ! |
92 |
|
93 |
debug=valid("pathcreate") |
94 |
print=valid("printgeom") |
95 |
printspline=(valid("printspline").AND.(dist<=1e30)) |
96 |
|
97 |
if (debug) Call Header("Entering Extrapol_int") |
98 |
|
99 |
! We want 100 points along the interpolating path |
100 |
NSpline=int(NMaxPtPath/100) |
101 |
if (printspline) THEN |
102 |
WRITE(TmpChar,'(I5)') Iopt |
103 |
FileSpline=Trim(adjustL(PathName)) // '_spline.' // AdjustL(TRIM(TmpChar)) |
104 |
OPEN(IOTMP,FILE=FileSpline) |
105 |
|
106 |
END IF |
107 |
|
108 |
ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),valzmat(Nat,3),DerInt(NCoord)) |
109 |
IdxGeom=1 |
110 |
|
111 |
XYZTmp2(1,1)=0. |
112 |
XYZTmp2(1,2)=0. |
113 |
XYZTmp2(1,3)=0. |
114 |
XYZTmp2(2,2)=0. |
115 |
XYZTmp2(2,3)=0. |
116 |
XYZTmp2(3,3)=0. |
117 |
|
118 |
valzmat=0. |
119 |
valzmat(2,1)=IntCoordI(1,1) |
120 |
valzmat(3,1)=IntCoordI(1,2) |
121 |
valzmat(3,2)=IntCoordI(1,3)*180./Pi |
122 |
Idx=4 |
123 |
DO I=4,Nat |
124 |
ValZmat(I,1)=IntCoordI(1,Idx) |
125 |
Idx=Idx+1 |
126 |
DO J=2,3 |
127 |
ValZmat(I,J)=IntCoordI(1,Idx)*180./Pi |
128 |
Idx=Idx+1 |
129 |
END DO |
130 |
END DO |
131 |
|
132 |
XyzTmp2(2,1)=valzmat(2,1) |
133 |
d=valzmat(3,1) |
134 |
a_val=valzmat(3,2)/180.*Pi |
135 |
! write(*,*) "aval,pi",a_val,valzmat(3,2),pi |
136 |
if (Nat.GE.3) THEN |
137 |
if (IndZmat(3,2).EQ.1) THEN |
138 |
XyzTmp2(3,1)=XYzTmp2(1,1)+d*cos(a_val) |
139 |
ELSE |
140 |
XyzTmp2(3,1)=XyzTmp2(2,1)-d*cos(a_val) |
141 |
ENDIF |
142 |
XyzTmp2(3,2)=d*sin(a_val) |
143 |
ENDIF |
144 |
! i=1 |
145 |
! WRITE(*,*) 'TOTOCart:',i, (XYzTMP2(I,J),J=1,3) |
146 |
! WRITE(*,*) 'TOTOZma:',i, (valzmat(I,J),J=1,3) |
147 |
! i=2 |
148 |
! WRITE(*,*) 'TOTOCart:',i, (XYzTMP2(I,J),J=1,3) |
149 |
! WRITE(*,*) 'TOTOZma:',i, (valzmat(I,J),J=1,3) |
150 |
! i=3 |
151 |
! WRITE(*,*) 'TOTOCart:',i, (XYzTMP2(I,J),J=1,3) |
152 |
! WRITE(*,*) 'TOTOZma:',i, (valzmat(I,J),J=1,3) |
153 |
|
154 |
DO i=4,Nat |
155 |
call ConvertZmat_cart(i,IndZmat,valzmat, & |
156 |
XYzTMP2(1,1), XYzTMP2(1,2),XYzTMP2(1,3)) |
157 |
! WRITE(*,*) 'TOTOZma:',i,IndZmat(I,1), & |
158 |
! (IndZmat(I,J+1),valzmat(I,J),J=1,3) |
159 |
! WRITE(*,*) 'TOTOCart:',i, (XYzTMP2(I,J),J=1,3) |
160 |
END DO |
161 |
|
162 |
! We align this geometry with the original one |
163 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
164 |
! PFL 2013 Feb 27 ... or if the user asks for it |
165 |
IF ((Nat.GE.4).OR.Align) THEN |
166 |
! The rotation matrix MRot has INTENT(OUT) in subroutine rotation_matrix(...), |
167 |
! which is called in the CalcRmsd(...). |
168 |
! PFL 24 Nov 2008 -> |
169 |
! If we have frozen atoms we align only those ones. |
170 |
if (NFroz.GT.0) THEN |
171 |
Call AlignPartial(Nat,x0,y0,z0, & |
172 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
173 |
FrozAtoms,MRot) |
174 |
ELSE |
175 |
Call CalcRmsd(Nat, x0,y0,z0, & |
176 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
177 |
MRot,rmsd,.TRUE.,.TRUE.) |
178 |
END IF |
179 |
! <- PFL 24 Nov 2008 |
180 |
END IF |
181 |
|
182 |
XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
183 |
IntCoordF(IdxGeom,:)=IntCoordI(1,:) |
184 |
|
185 |
! We calculate the first derivatives |
186 |
u=0.d0 |
187 |
DO Idx=1,NCoord |
188 |
call splintder(u,v,DerInt(iDX),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx)) |
189 |
END DO |
190 |
IntTangent(IdxGeom,:)=DerInt |
191 |
|
192 |
if (print.AND.(Dist.LE.1e20)) THEN |
193 |
WRITE(IOOUT,'(1X,I5)') Nat |
194 |
WRITE(IOOUT,*) "# Cartesian Coordinates for geom",IdxGeom |
195 |
DO i=1,Nat |
196 |
If (Renum) THEN |
197 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
198 |
(XyzTmp2(Order(I),J),J=1,3) |
199 |
ELSE |
200 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), & |
201 |
(XyzTmp2(I,J),J=1,3) |
202 |
END IF |
203 |
END DO |
204 |
END IF |
205 |
|
206 |
! We initialize the first geometry |
207 |
! PFL 26 Nov 2008 -> |
208 |
! Now, I copy XyzTmp2 into XyzTmp because XyzTmp2 has been aligned |
209 |
! with the reference geometry |
210 |
|
211 |
XyzTmp=XyzTmp2 |
212 |
|
213 |
! XyzTmp(1,1)=0. |
214 |
! XyzTmp(1,2)=0. |
215 |
! XyzTmp(1,3)=0. |
216 |
! XyzTmp(2,2)=0. |
217 |
! XyzTmp(2,3)=0. |
218 |
! XyzTmp(3,3)=0. |
219 |
|
220 |
! XyzTmp(2,1)=valzmat(2,1) |
221 |
! d=valzmat(3,1) |
222 |
! a_val=valzmat(3,2)/180.*Pi |
223 |
|
224 |
! if (Nat.GE.3) THEN |
225 |
! if (IndZmat(3,2).EQ.1) THEN |
226 |
! XyzTmp(3,1)=XYzTmp(1,1)+d*cos(a_val) |
227 |
! ELSE |
228 |
! XyzTmp(3,1)=XyzTmp(2,1)-d*cos(a_val) |
229 |
! ENDIF |
230 |
! XyzTmp(3,2)=d*sin(a_val) |
231 |
! ENDIF |
232 |
|
233 |
! DO i=4,Nat |
234 |
! call ConvertZmat_cart(i,IndZmat,valzmat, & |
235 |
! XYzTMP(1,1), XYzTMP(1,2),XYzTMP(1,3)) |
236 |
! END DO |
237 |
|
238 |
! <- PFL 26 Nov 2008 |
239 |
|
240 |
s=0. |
241 |
if (printspline) THEN |
242 |
SELECT CASE (Nat) |
243 |
CASE(2) |
244 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1) |
245 |
CASE (3) |
246 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1),valzmat(3,1:2) |
247 |
CASE(4:) |
248 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1),valzmat(3,1:2),valzmat(4:Nat,1:3) |
249 |
END SELECT |
250 |
END IF |
251 |
valzmat=0.d0 |
252 |
|
253 |
DO K=1,NMaxPtPath |
254 |
u=real(K)/NMaxPtPath*(NGeomI-1.) |
255 |
|
256 |
XYZTmp2(1,1)=0. |
257 |
XYZTmp2(1,2)=0. |
258 |
XYZTmp2(1,3)=0. |
259 |
XYZTmp2(2,2)=0. |
260 |
XYZTmp2(2,3)=0. |
261 |
XYZTmp2(3,3)=0. |
262 |
|
263 |
! We generate the interpolated Zmatrix |
264 |
call splintder(u,v,DerInt(1),NGeomI,xgeom(1),IntCoordI(1,1),Coef(1,1)) |
265 |
valzmat(2,1)=v |
266 |
call splintder(u,v,DerInt(2),NGeomI,xgeom(1),IntCoordI(1,2),Coef(1,2)) |
267 |
valzmat(3,1)=v |
268 |
call splintder(u,v,DerInt(3),NGeomI,xgeom(1),IntCoordI(1,3),Coef(1,3)) |
269 |
valzmat(3,2)=v*180./Pi |
270 |
Idx=4 |
271 |
DO I=4,Nat |
272 |
call splintder(u,v,DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx)) |
273 |
valzmat(I,1)=v |
274 |
Idx=Idx+1 |
275 |
DO J=2,3 |
276 |
call splintder(u,v,DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx)) |
277 |
valzmat(I,J)=v*180./pi |
278 |
Idx=Idx+1 |
279 |
END DO |
280 |
END DO ! matches DO I=4,Nat |
281 |
|
282 |
! We convert it into Cartesian coordinates |
283 |
XyzTmp2(2,1)=valzmat(2,1) |
284 |
d=valzmat(3,1) |
285 |
a_val=valzmat(3,2)/180.*Pi |
286 |
if (Nat.GE.3) THEN |
287 |
if (IndZmat(3,2).EQ.1) THEN |
288 |
XyzTmp2(3,1)=XYzTmp2(1,1)+d*cos(a_val) |
289 |
ELSE |
290 |
XyzTmp2(3,1)=XyzTmp2(2,1)-d*cos(a_val) |
291 |
ENDIF |
292 |
XyzTmp2(3,2)=d*sin(a_val) |
293 |
ENDIF |
294 |
|
295 |
DO I=4,Nat |
296 |
call ConvertZmat_cart(I,IndZmat,valzmat, & |
297 |
XYzTMP2(1,1), XYzTMP2(1,2),XYzTMP2(1,3)) |
298 |
END DO |
299 |
|
300 |
IF ((Nat.GE.4).OR.Align) THEN |
301 |
! PFL 24 Nov 2008 -> |
302 |
! If we have frozen atoms we align only those ones. |
303 |
if (NFroz.GT.0) THEN |
304 |
Call AlignPartial(Nat,x0,y0,z0, & |
305 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
306 |
FrozAtoms,MRot) |
307 |
ELSE |
308 |
! PFL 26 Nov 2008! |
309 |
! Note to myself: in Extrapol_cart we always align on x0,y0,z0 but here |
310 |
! we align on the previous geom... what is the best ? Is there a difference ? |
311 |
Call CalcRmsd(Nat, XyzTmp(1:Nat,1),XyzTmp(1:Nat,2),XyzTmp(1:Nat,3), & |
312 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
313 |
MRot,rmsd,.TRUE.,.TRUE.) |
314 |
END IF |
315 |
! <- PFL 24 Nov 2008 |
316 |
END IF |
317 |
|
318 |
ds=0. |
319 |
DO I=1,Nat |
320 |
DO J=1,3 |
321 |
ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2 |
322 |
XYZTmp(I,J)=XyzTMP2(I,J) |
323 |
END DO |
324 |
END DO |
325 |
|
326 |
|
327 |
|
328 |
s=s+sqrt(ds) |
329 |
|
330 |
if ((printspline).AND.(MOD(K,NSpline).EQ.0)) THEN |
331 |
SELECT CASE (Nat) |
332 |
CASE(2) |
333 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1) |
334 |
CASE (3) |
335 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1),valzmat(3,1:2) |
336 |
CASE(4:) |
337 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1),valzmat(3,1:2),valzmat(4:Nat,1:3) |
338 |
END SELECT |
339 |
END IF |
340 |
|
341 |
! if (debug) WRITE(*,*) "Debug u,s,dist",u,s,dist |
342 |
if (s>=dist) THEN |
343 |
if (debug) THEN |
344 |
WRITE(*,*) "DBG Zmat",s |
345 |
WRITE(*,'(1X,I5)') IndZmat(1,1) |
346 |
WRITE(*,'(1X,I5,I5,1X,F10.4)') IndZmat(2,1),IndZmat(2,2),valzmat(2,1) |
347 |
WRITE(*,'(1X,I5,2(I5,1X,F10.4))') IndZmat(3,1),IndZmat(3,2),valzmat(3,1) & |
348 |
,IndZmat(3,3),valzmat(3,2) |
349 |
DO I=4,Nat |
350 |
WRITE(*,'(1X,I5,3(I5,1X,F10.4))') IndZmat(I,1),IndZmat(I,2),valzmat(I,1) & |
351 |
,IndZmat(I,3),valzmat(I,2),IndZmat(I,4),valzmat(I,3) |
352 |
END DO |
353 |
END IF ! matches if (debug) THEN |
354 |
|
355 |
s=s-dist |
356 |
IdxGeom=IdxGeom+1 |
357 |
SGeom(IdxGeom)=s+IdxGeom*dist |
358 |
XgeomF(IdxGeom)=u |
359 |
XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
360 |
IntCoordF(IdxGeom,1)=valzmat(2,1) |
361 |
IntCoordF(IdxGeom,2)=valzmat(3,1) |
362 |
IntCoordF(IdxGeom,3)=valzmat(3,2)/180.*Pi |
363 |
Idx=4 |
364 |
DO I=4,Nat |
365 |
IntCoordF(IdxGeom,Idx)=valzmat(I,1) |
366 |
IntCoordF(IdxGeom,Idx+1)=valzmat(I,2)/180.*Pi |
367 |
IntCoordF(IdxGeom,Idx+2)=valzmat(I,3)/180.*Pi |
368 |
Idx=Idx+3 |
369 |
END DO |
370 |
IntTangent(IdxGeom,:)=DerInt |
371 |
|
372 |
if (print) THEN |
373 |
WRITE(IOOUT,'(1X,I5)') Nat |
374 |
WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K |
375 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
376 |
IF ((Nat.GE.4).OR.Align) THEN |
377 |
! PFL 24 Nov 2008 -> |
378 |
! If we have frozen atoms we align only those ones. |
379 |
if (NFroz.GT.0) THEN |
380 |
Call AlignPartial(Nat,x0,y0,z0, & |
381 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
382 |
FrozAtoms,MRot) |
383 |
ELSE |
384 |
Call CalcRmsd(Nat, x0,y0,z0, & |
385 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
386 |
MRot,rmsd,.TRUE.,.TRUE.) |
387 |
END IF |
388 |
! <- PFL 24 Nov 2008 |
389 |
|
390 |
END IF |
391 |
|
392 |
DO I=1,Nat |
393 |
If (Renum) THEN |
394 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
395 |
(XyzTmp2(Order(I),J),J=1,3) |
396 |
ELSE |
397 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), & |
398 |
(XyzTmp2(I,J),J=1,3) |
399 |
END IF |
400 |
END DO |
401 |
|
402 |
END IF ! matches if (print) THEN |
403 |
END IF ! matches if (s>=dist) THEN |
404 |
END DO ! matches DO K=1,NMaxPtPath, Is it correct?? |
405 |
|
406 |
|
407 |
if (printspline) THEN |
408 |
SELECT CASE (Nat) |
409 |
CASE(2) |
410 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1) |
411 |
CASE (3) |
412 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1),valzmat(3,1:2) |
413 |
CASE(4:) |
414 |
WRITE(IOTMP,'(15(1X,F10.5))') s,valzmat(2,1),valzmat(3,1:2),valzmat(4:Nat,1:3) |
415 |
END SELECT |
416 |
END IF |
417 |
|
418 |
if (s>=0.9*dist) THEN |
419 |
if (debug) WRITE(*,*) "DBG Extrapol_int L383: Adding last geom" |
420 |
if (debug) write(*,*) "Extrapol_int u,xgeom(NGeomI),s,dist,s-dist",u,xgeom(NGeomI),s,dist,s-dist |
421 |
! u=xgeom(NGeomI) |
422 |
s=s-dist |
423 |
|
424 |
|
425 |
! ! We generate the interpolated Zmatrix |
426 |
! call splintder(u,v,DerInt(1),NGeomI,xgeom(1),IntCoordI(1,1),Coef(1,1)) |
427 |
! valzmat(2,1)=v |
428 |
! call splintder(u,v,DerInt(2),NGeomI,xgeom(1),IntCoordI(1,2),Coef(1,2)) |
429 |
! valzmat(3,1)=v |
430 |
! call splintder(u,v,DerInt(3),NGeomI,xgeom(1),IntCoordI(1,3),Coef(1,3)) |
431 |
! valzmat(3,2)=v*180./Pi |
432 |
! Idx=4 |
433 |
! DO I=4,Nat |
434 |
! call splintder(u,v,DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx)) |
435 |
! valzmat(I,1)=v |
436 |
! Idx=Idx+1 |
437 |
! DO J=2,3 |
438 |
! call splintder(u,v,DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx)) |
439 |
! valzmat(I,J)=v*180./pi |
440 |
! Idx=Idx+1 |
441 |
! END DO |
442 |
! END DO ! matches DO I=4,Nat |
443 |
|
444 |
! ! We convert it into Cartesian coordinates |
445 |
! XyzTmp2(2,1)=valzmat(2,1) |
446 |
! d=valzmat(3,1) |
447 |
! a_val=valzmat(3,2)/180.*Pi |
448 |
! if (Nat.GE.3) THEN |
449 |
! if (IndZmat(3,2).EQ.1) THEN |
450 |
! XyzTmp2(3,1)=XYzTmp2(1,1)+d*cos(a_val) |
451 |
! ELSE |
452 |
! XyzTmp2(3,1)=XyzTmp2(2,1)-d*cos(a_val) |
453 |
! ENDIF |
454 |
! XyzTmp2(3,2)=d*sin(a_val) |
455 |
! ENDIF |
456 |
|
457 |
! DO I=4,Nat |
458 |
! call ConvertZmat_cart(I,IndZmat,valzmat, & |
459 |
! XYzTMP2(1,1), XYzTMP2(1,2),XYzTMP2(1,3)) |
460 |
! END DO |
461 |
|
462 |
! IF (Nat.GE.4) THEN |
463 |
! ! PFL 24 Nov 2008 -> |
464 |
! ! If we have frozen atoms we align only those ones. |
465 |
! if (NFroz.GT.0) THEN |
466 |
! Call AlignPartial(Nat,x0,y0,z0, & |
467 |
! xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
468 |
! FrozAtoms,MRot) |
469 |
! ELSE |
470 |
! ! PFL 26 Nov 2008! |
471 |
! ! Note to myself: in Extrapol_cart we always align on x0,y0,z0 but here |
472 |
! ! we align on the previous geom... what is the best ? Is there a difference ? |
473 |
! Call CalcRmsd(Nat, XyzTmp(1:Nat,1),XyzTmp(1:Nat,2),XyzTmp(1:Nat,3), & |
474 |
! xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
475 |
! MRot,rmsd,.TRUE.,.TRUE.) |
476 |
! END IF |
477 |
! ! <- PFL 24 Nov 2008 |
478 |
! END IF |
479 |
|
480 |
IdxGeom=IdxGeom+1 |
481 |
|
482 |
|
483 |
|
484 |
IF (IdxGeom.GT.NGeomF) THEN |
485 |
WRITE(IOOUT,*) "!!! ERROR in Extrapol_int !!!!" |
486 |
WRITE(IOOUT,*) "Too many structures. Increase NMaxPath" |
487 |
WRITE(*,*) "** PathCreate ***" |
488 |
WRITE(*,*) "Distribution of points along the path is wrong." |
489 |
WRITE(*,*) "Increase value of NMaxPtPath in the input file" |
490 |
WRITE(*,*) "Present value is:", NMaxPtPath |
491 |
STOP |
492 |
END IF |
493 |
|
494 |
SGeom(IdxGeom)=s+IdxGeom*dist |
495 |
XgeomF(IdxGeom)=min(u,NGeomI-1.d0) |
496 |
XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
497 |
! XyzGeomF(IdxGeom,:,:)=XyzTmp2(:,:) |
498 |
IntCoordF(IdxGeom,1)=valzmat(2,1) |
499 |
IntCoordF(IdxGeom,2)=valzmat(3,1) |
500 |
IntCoordF(IdxGeom,3)=valzmat(3,2)/180.*Pi |
501 |
Idx=4 |
502 |
DO I=4,Nat |
503 |
IntCoordF(IdxGeom,Idx)=valzmat(I,1) |
504 |
IntCoordF(IdxGeom,Idx+1)=valzmat(I,2)/180.*Pi |
505 |
IntCoordF(IdxGeom,Idx+2)=valzmat(I,3)/180.*Pi |
506 |
Idx=Idx+3 |
507 |
END DO |
508 |
IntTangent(IdxGeom,:)=DerInt |
509 |
|
510 |
if (print) THEN |
511 |
WRITE(IOOUT,'(1X,I5)') Nat |
512 |
WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K |
513 |
! PFL 17/July/2006: only if we have more than 4 atoms. |
514 |
IF ((Nat.GE.4).OR.Align) THEN |
515 |
! PFL 24 Nov 2008 -> |
516 |
! If we have frozen atoms we align only those ones. |
517 |
if (NFroz.GT.0) THEN |
518 |
Call AlignPartial(Nat,x0,y0,z0, & |
519 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
520 |
FrozAtoms,MRot) |
521 |
ELSE |
522 |
Call CalcRmsd(Nat, x0,y0,z0, & |
523 |
xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
524 |
MRot,rmsd,.TRUE.,.TRUE.) |
525 |
END IF |
526 |
! <- PFL 24 Nov 2008 |
527 |
END IF |
528 |
|
529 |
DO I=1,Nat |
530 |
If (Renum) THEN |
531 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
532 |
(XyzTmp2(Order(I),J),J=1,3) |
533 |
ELSE |
534 |
WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), & |
535 |
(XyzTmp2(I,J),J=1,3) |
536 |
END IF |
537 |
END DO ! matches DO I=1,Nat |
538 |
END IF ! matches if (print) THEN |
539 |
END IF ! matches if (s>=0.9*dist) THEN |
540 |
|
541 |
if (debug) WRITE(*,*) 's final =',s |
542 |
|
543 |
DEALLOCATE(XyzTmp,XyzTmp2,valzmat) |
544 |
|
545 |
if (printspline) CLOSE(IOTMP) |
546 |
|
547 |
if (debug) Call Header("Extrapol_int Over") |
548 |
|
549 |
|
550 |
END SUBROUTINE EXTRAPOL_INT |