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