root / src / Extrapol_mixed.f90
Historique | Voir | Annoter | Télécharger (7,72 ko)
1 | 1 | pfleura2 | SUBROUTINE Extrapol_mixed(s,dist,x0,y0,z0,xgeom,Coef) |
---|---|---|---|
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 |
6 | 1 | pfleura2 | ! length of the path |
7 | 1 | pfleura2 | ! ii) dist finite, it will give you the images you want along the path. |
8 | 1 | pfleura2 | ! |
9 | 1 | pfleura2 | ! For now, it gives equidistant geometries |
10 | 1 | pfleura2 | !!!!!!!!!!!!!!!! |
11 | 1 | pfleura2 | ! |
12 | 1 | pfleura2 | ! v2.0 |
13 | 1 | pfleura2 | ! Uses Mix2cart for conversions. |
14 | 1 | pfleura2 | |
15 | 12 | pfleura2 | !---------------------------------------------------------------------- |
16 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
17 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
18 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
19 | 12 | pfleura2 | ! |
20 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
21 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
22 | 12 | pfleura2 | ! |
23 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
24 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
25 | 12 | pfleura2 | ! |
26 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
27 | 12 | pfleura2 | ! |
28 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
29 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
30 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
31 | 12 | pfleura2 | ! or (at your option) any later version. |
32 | 12 | pfleura2 | ! |
33 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
34 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
35 | 12 | pfleura2 | ! |
36 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
37 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
38 | 12 | pfleura2 | ! |
39 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
40 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
41 | 12 | pfleura2 | ! |
42 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
43 | 12 | pfleura2 | ! for commercial licensing opportunities. |
44 | 12 | pfleura2 | !---------------------------------------------------------------------- |
45 | 1 | pfleura2 | |
46 | 12 | pfleura2 | |
47 | 1 | pfleura2 | use Path_module |
48 | 1 | pfleura2 | use Io_module |
49 | 1 | pfleura2 | |
50 | 1 | pfleura2 | |
51 | 1 | pfleura2 | IMPLICIT NONE |
52 | 1 | pfleura2 | |
53 | 1 | pfleura2 | |
54 | 1 | pfleura2 | REAL(KREAL), INTENT(OUT) :: s |
55 | 1 | pfleura2 | REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat) |
56 | 1 | pfleura2 | REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord) |
57 | 1 | pfleura2 | |
58 | 1 | pfleura2 | INTEGER(KINT) :: IdxGeom, I, J, K, Idx |
59 | 2 | pfleura2 | REAL(KREAL) :: Rmsd, MRot(3, 3), ds, u |
60 | 1 | pfleura2 | |
61 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:) ! (Nat,3) |
62 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: IntCoordTmp(:),DerInt(:) ! (NCoord) |
63 | 1 | pfleura2 | |
64 | 1 | pfleura2 | |
65 | 1 | pfleura2 | LOGICAL :: debug, print |
66 | 1 | pfleura2 | LOGICAL, EXTERNAL :: valid |
67 | 1 | pfleura2 | |
68 | 1 | pfleura2 | !We will calculate the length of the path, in MW coordinates... |
69 | 1 | pfleura2 | ! this is done is a stupid way: we interpolate the zmatrix values, |
70 | 1 | pfleura2 | ! convert them into cartesian, weight the cartesian |
71 | 1 | pfleura2 | ! and calculate the evolution of the distance ! |
72 | 1 | pfleura2 | ! We have to follow the same procedure for every geometry |
73 | 1 | pfleura2 | ! so even for the first one, we have to convert it from zmat |
74 | 1 | pfleura2 | ! to cartesian ! |
75 | 1 | pfleura2 | |
76 | 1 | pfleura2 | debug=valid("pathcreate") |
77 | 1 | pfleura2 | print=valid("printgeom") |
78 | 1 | pfleura2 | |
79 | 1 | pfleura2 | if (debug) Call Header("Entering Extrapol_mixed") |
80 | 1 | pfleura2 | if (debug) WRITE(*,*) "NFroz,NCart",NFroz,NCart |
81 | 1 | pfleura2 | ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),IntCoordTmp(NCoord),DerInt(NCoord)) |
82 | 1 | pfleura2 | IdxGeom=1 |
83 | 1 | pfleura2 | |
84 | 1 | pfleura2 | IntCoordTmp=IntCoordI(1,1:NCoord) |
85 | 1 | pfleura2 | call Mixed2Cart(Nat,IndZmat,IntCoordTmp,XyzTmp2(1,1)) |
86 | 1 | pfleura2 | |
87 | 1 | pfleura2 | XyzTmp=XyzTmp2 |
88 | 1 | pfleura2 | |
89 | 1 | pfleura2 | ! We align this geometry with the original one |
90 | 1 | pfleura2 | ! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms |
91 | 1 | pfleura2 | ! PFL 17/July/2006: only if we have more than 4 atoms. |
92 | 1 | pfleura2 | IF ((NCart.LT.3).AND.(Nat.GT.4)) THEN |
93 | 1 | pfleura2 | ! IF (Nat.GT.4) THEN |
94 | 1 | pfleura2 | Call CalcRmsd(Nat, x0,y0,z0, & |
95 | 1 | pfleura2 | xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
96 | 1 | pfleura2 | MRot,rmsd,FRot,FAlign) |
97 | 1 | pfleura2 | END IF |
98 | 1 | pfleura2 | |
99 | 1 | pfleura2 | XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
100 | 1 | pfleura2 | IntCoordF(IdxGeom,:)=IntCoordI(1,:) |
101 | 1 | pfleura2 | |
102 | 1 | pfleura2 | if (print.AND.(Dist.LE.1e20)) THEN |
103 | 1 | pfleura2 | WRITE(IOOUT,'(1X,I5)') Nat |
104 | 1 | pfleura2 | WRITE(IOOUT,*) "# Cartesian Coordinates for geom",IdxGeom |
105 | 1 | pfleura2 | DO i=1,Nat |
106 | 1 | pfleura2 | If (Renum) THEN |
107 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
108 | 1 | pfleura2 | (XyzTmp2(Order(I),J),J=1,3) |
109 | 1 | pfleura2 | ELSE |
110 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), & |
111 | 1 | pfleura2 | (XyzTmp2(I,J),J=1,3) |
112 | 1 | pfleura2 | END IF |
113 | 1 | pfleura2 | END DO |
114 | 1 | pfleura2 | END IF |
115 | 1 | pfleura2 | |
116 | 1 | pfleura2 | ! Calculate tangents for first geometry |
117 | 1 | pfleura2 | u=0.d0 |
118 | 1 | pfleura2 | DO Idx=1,NCoord |
119 | 1 | pfleura2 | call splintder(u,IntCoordTmp(Idx),DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx)) |
120 | 1 | pfleura2 | END DO |
121 | 1 | pfleura2 | IntTangent(IdxGeom,:)=DerInt |
122 | 1 | pfleura2 | |
123 | 1 | pfleura2 | |
124 | 1 | pfleura2 | ! First geometry already initialized |
125 | 1 | pfleura2 | |
126 | 1 | pfleura2 | s=0. |
127 | 1 | pfleura2 | ! valzmat=0.d0 |
128 | 1 | pfleura2 | |
129 | 1 | pfleura2 | DO K=1,NMaxPtPath |
130 | 1 | pfleura2 | u=real(K)/NMaxPtPath*(NGeomI-1.) |
131 | 1 | pfleura2 | |
132 | 1 | pfleura2 | XYZTmp2=0. |
133 | 1 | pfleura2 | |
134 | 1 | pfleura2 | ! We generate the interpolated coordinates |
135 | 1 | pfleura2 | DO Idx=1,NCoord |
136 | 1 | pfleura2 | call splintder(u,IntCoordTmp(Idx),DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx)) |
137 | 1 | pfleura2 | END DO |
138 | 1 | pfleura2 | |
139 | 1 | pfleura2 | ! We convert it into Cartesian coordinates |
140 | 1 | pfleura2 | call Mixed2Cart(Nat,IndZmat,IntCoordTmp,XyzTmp2(1,1)) |
141 | 1 | pfleura2 | |
142 | 1 | pfleura2 | ! We calculate ds |
143 | 1 | pfleura2 | ds=0. |
144 | 1 | pfleura2 | DO I=1,Nat |
145 | 1 | pfleura2 | DO J=1,3 |
146 | 1 | pfleura2 | ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2 |
147 | 1 | pfleura2 | XYZTmp(I,J)=XyzTMP2(I,J) |
148 | 1 | pfleura2 | ENDDO |
149 | 1 | pfleura2 | ENDDO |
150 | 1 | pfleura2 | s=s+sqrt(ds) |
151 | 1 | pfleura2 | |
152 | 1 | pfleura2 | ! if (debug) WRITE(*,*) "Debug u,s,dist",u,s,dist |
153 | 1 | pfleura2 | if (s>=dist) THEN |
154 | 1 | pfleura2 | s=s-dist |
155 | 1 | pfleura2 | IdxGeom=IdxGeom+1 |
156 | 7 | pfleura2 | SGeom(IdxGeom)=s+IdxGeom*dist |
157 | 1 | pfleura2 | XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
158 | 1 | pfleura2 | |
159 | 1 | pfleura2 | IntCoordF(IdxGeom,:)=IntCoordTmp |
160 | 1 | pfleura2 | IntTangent(IdxGeom,:)=DerInt |
161 | 1 | pfleura2 | |
162 | 1 | pfleura2 | if (print) THEN |
163 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A,12(1X,F10.5))') "#Internal Coord",IntCoordTmp(1:NCoord) |
164 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A,12(1X,F10.5))') "#Internal tan",IntTangent(IdxGeom,1:NCoord) |
165 | 1 | pfleura2 | WRITE(IOOUT,'(1X,I5)') Nat |
166 | 1 | pfleura2 | WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K,u,Xgeom(NGeomI) |
167 | 1 | pfleura2 | |
168 | 1 | pfleura2 | ! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms |
169 | 1 | pfleura2 | ! PFL 17/July/2006: only if we have more than 4 atoms. |
170 | 1 | pfleura2 | IF ((NCart.LT.3).AND.(Nat.GT.4)) THEN |
171 | 1 | pfleura2 | ! IF (Nat.GT.4) THEN |
172 | 1 | pfleura2 | Call CalcRmsd(Nat, x0,y0,z0, & |
173 | 1 | pfleura2 | xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
174 | 1 | pfleura2 | MRot,rmsd,FRot,FAlign) |
175 | 1 | pfleura2 | END IF |
176 | 1 | pfleura2 | |
177 | 1 | pfleura2 | DO i=1,Nat |
178 | 1 | pfleura2 | If (Renum) THEN |
179 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
180 | 1 | pfleura2 | (XyzTmp2(Order(I),J),J=1,3) |
181 | 1 | pfleura2 | ELSE |
182 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), & |
183 | 1 | pfleura2 | (XyzTmp2(I,J),J=1,3) |
184 | 1 | pfleura2 | END IF |
185 | 1 | pfleura2 | END DO |
186 | 1 | pfleura2 | |
187 | 1 | pfleura2 | END IF |
188 | 1 | pfleura2 | END IF |
189 | 7 | pfleura2 | END DO |
190 | 1 | pfleura2 | |
191 | 1 | pfleura2 | |
192 | 1 | pfleura2 | if ((s>=0.1*dist).AND.(IdxGeom.EQ.NGeomF)) THEN |
193 | 1 | pfleura2 | WRITE(*,*) "** PathCreate ***" |
194 | 1 | pfleura2 | WRITE(*,*) "Distribution of points along the path is wrong." |
195 | 1 | pfleura2 | WRITE(*,*) "Increase value of NMaxPtPath in the input file" |
196 | 1 | pfleura2 | WRITE(*,*) "Present value is:", NMaxPtPath |
197 | 1 | pfleura2 | STOP |
198 | 1 | pfleura2 | END IF |
199 | 1 | pfleura2 | |
200 | 1 | pfleura2 | IdxGeom=NGeomF |
201 | 1 | pfleura2 | |
202 | 1 | pfleura2 | ! We have to add the last geometry. We copy the last geom of Initial geometries. |
203 | 7 | pfleura2 | IntCoordF(IdxGeom,:)=IntCoordI(NGeomI,:) |
204 | 7 | pfleura2 | IntTangent(IdxGeom,:)=DerInt |
205 | 1 | pfleura2 | |
206 | 1 | pfleura2 | ! we convert it to cartesian geom |
207 | 1 | pfleura2 | call Mixed2Cart(Nat,IndZmat,IntCoordF(IdxGeom,1),XyzTmp2(1,1)) |
208 | 1 | pfleura2 | XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/)) |
209 | 1 | pfleura2 | |
210 | 1 | pfleura2 | if (print) THEN |
211 | 1 | pfleura2 | WRITE(IOOUT,'(1X,I5)') Nat |
212 | 1 | pfleura2 | WRITE(IOOUT,*) "# Cartesian coord for last Geometry ",IdxGeom,K,u,Xgeom(NGeomI) |
213 | 1 | pfleura2 | ! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms |
214 | 1 | pfleura2 | ! PFL 17/July/2006: only if we have more than 4 atoms. |
215 | 1 | pfleura2 | IF ((NCART.LT.3).AND.(Nat.GT.4)) THEN |
216 | 1 | pfleura2 | ! IF (Nat.GT.4) THEN |
217 | 1 | pfleura2 | Call CalcRmsd(Nat, x0,y0,z0, & |
218 | 1 | pfleura2 | xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), & |
219 | 1 | pfleura2 | MRot,rmsd,FRot,FAlign) |
220 | 1 | pfleura2 | END IF |
221 | 1 | pfleura2 | |
222 | 1 | pfleura2 | DO i=1,Nat |
223 | 1 | pfleura2 | If (Renum) THEN |
224 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), & |
225 | 1 | pfleura2 | (XyzTmp2(Order(I),J),J=1,3) |
226 | 1 | pfleura2 | ELSE |
227 | 1 | pfleura2 | WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), & |
228 | 1 | pfleura2 | (XyzTmp2(I,J),J=1,3) |
229 | 1 | pfleura2 | END IF |
230 | 1 | pfleura2 | END DO |
231 | 1 | pfleura2 | END IF |
232 | 1 | pfleura2 | |
233 | 1 | pfleura2 | |
234 | 1 | pfleura2 | if (debug) WRITE(*,*) 's final =',s |
235 | 1 | pfleura2 | |
236 | 1 | pfleura2 | DEALLOCATE(XyzTmp,XyzTmp2) |
237 | 1 | pfleura2 | |
238 | 1 | pfleura2 | if (debug) Call Header("Extrapol_Mixed Over") |
239 | 1 | pfleura2 | |
240 | 1 | pfleura2 | |
241 | 1 | pfleura2 | END SUBROUTINE EXTRAPOL_MIXED |