root / src / PathCreate.f90 @ 2
Historique | Voir | Annoter | Télécharger (35,64 ko)
1 |
!================================================================ |
---|---|
2 |
! |
3 |
! This subroutine create a path using starting geometries |
4 |
! it is 'original' in the sense that the path is generated |
5 |
! by interpolating internal coordinates instead of cartesian. |
6 |
! Comes from the Extrapol.f subroutine of Cart suite. |
7 |
! Rewritten in F90 to be more flexible |
8 |
! |
9 |
!================================================================ |
10 |
|
11 |
SUBROUTINE PathCreate(IOpt) |
12 |
|
13 |
use Io_module |
14 |
use Path_module, only : Nat, NGeomI, NCoord, NGeomF, IGeomRef, NMaxL, IReparam, IReparamT, & |
15 |
Coord, Frozen, Cart, NCart, NFroz, XyzGeomI, atome, r_cov, fact, & |
16 |
IndZmat, Renum, Order, OrderInv, IntCoordI, IntCoordF,Pi, BMat_BakerT, Nom, & |
17 |
Hess,IntFroz, ISpline, IntTangent, XyzGeomF, NPrim,Xprimitive_t, OptGeom, & |
18 |
UMatF, UMat_local, XyzTangent, Linear |
19 |
! BMat_BakerT (3*Nat,NCoord), XyzGeomI(NGeomI,3,Nat), IGeomRef=-1 (default value) |
20 |
! IntCoordI(NGeomI,NCoord) |
21 |
|
22 |
IMPLICIT NONE |
23 |
|
24 |
REAL(KREAL), PARAMETER :: Inf=1e32 |
25 |
INTEGER(KINT), INTENT(IN) :: IOpt |
26 |
|
27 |
INTEGER(KINT) :: at,long |
28 |
REAL(KREAL), ALLOCATABLE :: val_zmat(:,:), val_zmatTmp(:,:) ! (3,Nat) |
29 |
REAL(KREAL), ALLOCATABLE :: X0(:), Y0(:), Z0(:) ! Nat |
30 |
REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:) ! (Nat,3) |
31 |
! REAL(KREAL), ALLOCATABLE :: XyzTmp3(:,:) ! (3,Nat) |
32 |
REAL(KREAL), ALLOCATABLE :: IntCoordTmp(:) ! (NCoord) |
33 |
INTEGER(KINT), ALLOCATABLE :: IndZmat0(:,:) !Nat,5 |
34 |
REAL(KREAL), ALLOCATABLE :: Coef(:,:) ! (NGeomI,NCoord) |
35 |
! NPrim=Number of primitive coordinates. |
36 |
REAL(KREAL), ALLOCATABLE :: XGeom(:) ! NGeomI |
37 |
REAL(KREAL), ALLOCATABLE :: XGeomF(:) ! NGeomF |
38 |
REAL(KREAL), ALLOCATABLE :: Hess_int(:,:) ! Hess_int (3*Nat,3*Nat), used for Baker case |
39 |
INTEGER(KINT) :: NGeomS |
40 |
|
41 |
REAL(KREAL) :: Rmsd,MRot(3,3), Delta, normDeltaX_int |
42 |
REAL(KREAL), PARAMETER :: LimAngle=145.d0,TwoPi=360.d0 |
43 |
REAL(KREAL) ::s,ds,dist,a_val,d |
44 |
INTEGER(KINT) :: I,J,K,NbCycle,igeom,nb,ig,iat |
45 |
INTEGER(KINT) :: Itmp, Jat, L |
46 |
INTEGER(KINT) :: Idx,IBeg |
47 |
CHARACTER(LCHARS) :: Title |
48 |
REAL(KREAL), ALLOCATABLE :: x(:), y(:), z(:) |
49 |
LOGICAL :: debug, print |
50 |
LOGICAL, SAVE :: First=.TRUE. |
51 |
! Frozen contains the indices of frozen atoms |
52 |
LOGICAL, ALLOCATABLE :: FCart(:) ! Nat |
53 |
INTEGER, ALLOCATABLE :: AtCart(:) !Nat |
54 |
INTEGER(KINT), ALLOCATABLE :: LIAISONS(:,:),LiaisonsIni(:,:) ! (Nat,0:NMaxL) |
55 |
INTEGER(KINT), ALLOCATABLE :: Fragment(:),NbAtFrag(:) !nat |
56 |
INTEGER(KINT), ALLOCATABLE :: FragAt(:,:) !nat,nat |
57 |
INTEGER(KINT) :: NbFrag,NFragRef |
58 |
|
59 |
|
60 |
INTERFACE |
61 |
function valid(string) result (isValid) |
62 |
CHARACTER(*), intent(in) :: string |
63 |
logical :: isValid |
64 |
END function VALID |
65 |
|
66 |
FUNCTION test_zmat(na,ind_zmat) |
67 |
|
68 |
USE Path_module |
69 |
|
70 |
logical :: test_zmat |
71 |
integer(KINT) :: na |
72 |
integer(KINT) :: ind_zmat(Na,5) |
73 |
END FUNCTION TEST_ZMAT |
74 |
END INTERFACE |
75 |
|
76 |
|
77 |
|
78 |
debug=valid("pathcreate") |
79 |
print=valid("printgeom") |
80 |
if (debug) Call header("Entering PathCreate") |
81 |
if (debug.AND.First) WRITE(*,*) "= First call =" |
82 |
|
83 |
if (debug) WRITE(*,*) "Iopt,IReparam=",Iopt,IReparam |
84 |
|
85 |
ALLOCATE(Coef(NGeomI,NCoord),val_zmat(Nat,3),val_zmatTMP(Nat,3)) |
86 |
ALLOCATE(X0(Nat),Y0(Nat),Z0(Nat),Indzmat0(Nat,5)) |
87 |
ALLOCATE(X(Nat),Y(Nat),Z(Nat),Xgeom(NGeomI),XgeomF(NGeomF)) |
88 |
! ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),XyzTmp3(3,Nat)) |
89 |
ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3)) |
90 |
ALLOCATE(IntCoordTmp(NCoord)) |
91 |
|
92 |
Do I=1,NGeomI |
93 |
XGeom(I)=FLoat(I)-1.d0 |
94 |
END DO |
95 |
|
96 |
! First iteration of the optimization: |
97 |
IF (First) THEN ! matches at L484 |
98 |
if (debug) WRITE(*,*) "first iteration in PathCreate.90, L93" |
99 |
|
100 |
! This is the first call, so we might have to generate a Zmat |
101 |
First=.FALSE. |
102 |
|
103 |
IF ( ((COORD.EQ."ZMAT").OR.(COORD.EQ."HYBRID").OR.(COORD.EQ."MIXED") & |
104 |
.OR.(COORD.EQ."BAKER")).AND.(IGeomRef.LE.0)) THEN |
105 |
|
106 |
! User has not defined the Reference geometry, we have to choose it ourselves! |
107 |
! This is done by counting the number of fragments of each geometry. The |
108 |
! reference geometry is the one with the least fragments. When there are |
109 |
! frozen or cart atoms, they are discarded to count the fragments. |
110 |
|
111 |
ALLOCATE(Liaisons(Nat,0:NMaxL)) |
112 |
ALLOCATE(Fragment(nat),NbAtFrag(nat),FragAt(nat,nat),FCart(Nat)) |
113 |
FCart=.FALSE. |
114 |
! FCart(Nat) was under IF below earlier but is being accessed after this loop. |
115 |
IF ((Frozen(1).NE.0).OR.(Cart(1).NE.0)) THEN |
116 |
ALLOCATE(AtCart(Nat),LiaisonsIni(Nat,0:NMaxL)) |
117 |
FCart=.FALSE. |
118 |
NCart=0 |
119 |
Idx=1 |
120 |
DO WHILE (Frozen(Idx).NE.0) |
121 |
IF (Frozen(Idx).LT.0) THEN |
122 |
DO I=Frozen(Idx-1),abs(Frozen(Idx)) |
123 |
IF (.NOT.FCart(I)) THEN |
124 |
NCart=NCart+1 |
125 |
AtCart(NCart)=I |
126 |
FCart(I)=.TRUE. |
127 |
END IF |
128 |
END DO |
129 |
ELSE IF (.NOT.FCart(Frozen(Idx))) THEN |
130 |
FCart(Frozen(Idx))=.TRUE. |
131 |
NCart=NCart+1 |
132 |
AtCart(NCart)=Frozen(Idx) |
133 |
END IF |
134 |
Idx=Idx+1 |
135 |
END DO ! matches DO WHILE (Frozen(Idx).NE.0) |
136 |
NFroz=NCart |
137 |
Idx=1 |
138 |
DO WHILE (Cart(Idx).NE.0) |
139 |
IF (Cart(Idx).LT.0) THEN |
140 |
DO I=Cart(Idx-1),abs(Cart(Idx)) |
141 |
IF (.NOT.FCart(I)) THEN |
142 |
NCart=NCart+1 |
143 |
AtCart(NCart)=I |
144 |
FCart(I)=.TRUE. |
145 |
END IF |
146 |
END DO |
147 |
ELSEIF (.NOT.FCart(Cart(Idx))) THEN |
148 |
FCart(Cart(Idx))=.TRUE. |
149 |
NCart=NCart+1 |
150 |
AtCart(NCart)=Cart(Idx) |
151 |
END IF |
152 |
Idx=Idx+1 |
153 |
END DO !matches DO WHILE (Cart(Idx).NE.0) |
154 |
IF (debug) THEN |
155 |
WRITE(*,'(1X,A,I4,A,I4,A)') "DBG PathCreate - GeomRef :: Found ", & |
156 |
NFroz," frozen atoms, and a total of ",NCart, & |
157 |
" atoms described in cartesian coordinates" |
158 |
WRITE(*,*) "AtCart:",AtCart(1:NCart) |
159 |
END IF |
160 |
END IF ! IF ((Frozen(1).NE.0).OR.(Cart(1).NE.0)) THEN |
161 |
|
162 |
NFragRef=2*Nat |
163 |
DO IGeom=1,NGeomI |
164 |
x(1:Nat) = XyzGeomI(IGeom,1,1:Nat) |
165 |
y(1:Nat) = XyzGeomI(IGeom,2,1:Nat) |
166 |
z(1:Nat) = XyzGeomI(IGeom,3,1:Nat) |
167 |
! we calculate the connectivities |
168 |
Call CalcCnct(nat,atome,x,y,z,LIAISONS,r_cov,fact) |
169 |
! if needed, we get rid of links between cart or frozen atoms |
170 |
IF (NCart.GE.2) THEN |
171 |
LiaisonsIni=Liaisons |
172 |
DO I=1,NCart |
173 |
Iat=AtCart(I) |
174 |
if (debug) WRITE(*,'(20(1X,I3))') I,Iat, & |
175 |
(LiaisonsIni(Iat,Itmp),ITmp=0,LiaisonsIni(Iat,0)) |
176 |
DO J=1,LiaisonsIni(Iat,0) |
177 |
Jat=LiaisonsIni(Iat,J) |
178 |
IF (FCart(Jat)) THEN |
179 |
Call Annul(Liaisons,Iat,Jat) |
180 |
Call Annul(Liaisons,Jat,Iat) |
181 |
Call Annul(LiaisonsIni,Jat,Iat) |
182 |
Liaisons(Iat,0)=Liaisons(Iat,0)-1 |
183 |
Liaisons(Jat,0)=Liaisons(Jat,0)-1 |
184 |
LiaisonsIni(Jat,0)=LiaisonsIni(Jat,0)-1 |
185 |
END IF |
186 |
END DO |
187 |
END DO |
188 |
END IF ! matches IF (NCart.GE.2) THEN |
189 |
! we now calculate the number of fragments. |
190 |
Call Decomp_frag(nat,liaisons,.NOT.Fcart,nbfrag,Fragment,NbAtFrag,FragAt) |
191 |
IF (NbFrag.LT.NFragRef) THEN |
192 |
NFragRef=NbFrag |
193 |
! The reference geometry, IGeomRef, is determined based on the least number |
194 |
! of fragments (here if (((COORD.EQ."ZMAT").OR.(COORD.EQ."HYBRID").OR.(COORD |
195 |
!.EQ."MIXED")).AND.(IGeomRef.LE.0))), otherwise it still has the value of |
196 |
! IGeomRef=-1. |
197 |
IGeomRef=IGeom |
198 |
END IF |
199 |
END DO ! matches DO IGeom=1,NGeomI |
200 |
DEALLOCATE(FCart) |
201 |
END IF ! matches IF (((COORD.EQ."ZMAT").OR.(COORD.EQ."HYBRID").OR.(COORD.EQ."MIXED") |
202 |
! .OR.(COORD.EQ."BAKER")).AND.(IGeomRef.LE.0)). |
203 |
|
204 |
if (debug) WRITE(*,*) "DBG PathCreate : IGeomRef= ",IGeomRef |
205 |
|
206 |
! we now compute the internal coordinates for this geometry ! |
207 |
! The reference geometry, IGeomRef, is determined based on the least number |
208 |
! of fragments if (((COORD.EQ."ZMAT").OR.(COORD.EQ."HYBRID").OR.(COORD |
209 |
!.EQ."MIXED")).AND.(IGeomRef.LE.0)), otherwise it has the value of |
210 |
! IGeomRef=-1. |
211 |
x(1:Nat) = XyzGeomI(IGeomRef,1,1:Nat) ! XyzGeomI(NGeomI,3,Nat) |
212 |
y(1:Nat) = XyzGeomI(IGeomRef,2,1:Nat) |
213 |
z(1:Nat) = XyzGeomI(IGeomRef,3,1:Nat) |
214 |
|
215 |
IndZmat=0 |
216 |
IndZmat0=0 |
217 |
|
218 |
SELECT CASE(COORD) |
219 |
CASE ('BAKER') |
220 |
! atome(Nat), r_cov(0:Max_Z) |
221 |
! Frozen(Nat) contains the indices of frozen atoms |
222 |
Call Calc_baker(atome,r_cov,fact,frozen,IGeomRef) |
223 |
if (debug) THEN |
224 |
WRITE(*,*) "UMat_local after Calc_baker" |
225 |
DO I=1,3*Nat-6 |
226 |
WRITE(*,'(50(1X,F12.8))') UMat_local(:,I) |
227 |
END DO |
228 |
END IF |
229 |
DO IGeom=1,NGeomF |
230 |
UMatF(IGeom,:,:)=UMat_Local(:,:) |
231 |
END DO |
232 |
|
233 |
ALLOCATE(Xprimitive_t(NPrim)) |
234 |
! x, y, z corresponds the reference geometry. |
235 |
DO I=1,Nat |
236 |
Order(I)=I |
237 |
OrderInv(I)=I |
238 |
END DO |
239 |
x0=x |
240 |
y0=y |
241 |
z0=z |
242 |
CASE ('ZMAT','HYBRID') |
243 |
! IN case we are using Hybrid or zmat coordinate system, we have to |
244 |
! generate the internal coordinates with a Z-Matrix |
245 |
! IN case we have frozen atoms, we generate a constrained Zmat |
246 |
IF (Frozen(1).NE.0) THEN |
247 |
Renum=.True. |
248 |
call Calc_zmat_const_frag(Nat,atome,IndZmat0,val_zmat,x,y,z,r_cov,fact,frozen) |
249 |
ELSE |
250 |
!no zmat... we create our own |
251 |
call Calc_zmat_frag(Nat,atome,IndZmat0,val_zmat,x,y,z,r_cov,fact) |
252 |
if (valid('old_zmat')) THEN |
253 |
call Calc_zmat(Nat,atome,IndZmat0,val_zmat,x,y,z,r_cov,fact) |
254 |
WRITE(*,*) "DBG PathCreate Calc_Zmat.... STOP" |
255 |
STOP |
256 |
END IF |
257 |
END IF |
258 |
|
259 |
if (debug) WRITE(*,*) 'Back from Calc_zmat' |
260 |
IF (.NOT.test_zmat(nat,IndZmat0)) THEN |
261 |
WRITE(IOOUT,*) "I cannot generate a valid Zmat... help" |
262 |
STOP |
263 |
END IF |
264 |
|
265 |
! The IndZmat0 generated by Calc_zmat refers to the order of the input x,y,z |
266 |
! However, we need it with the new order so that we can use the zmat |
267 |
! coordinates to generate cartesian coordinates. |
268 |
! So, we have to reorder it... |
269 |
DO I=1,Nat |
270 |
Order(IndZmat0(I,1))=I |
271 |
OrderInv(I)=IndZmat0(I,1) |
272 |
! I let X0 being the Cartesian coordinates of the reference geometry. Before it was |
273 |
! those of the First geometry (which was also the reference one). This might change! |
274 |
X0(i)=X(IndZmat0(i,1)) |
275 |
Y0(i)=Y(IndZmat0(i,1)) |
276 |
Z0(i)=Z(IndZmat0(i,1)) |
277 |
END DO |
278 |
IndZmat(1,1)=Order(IndZmat0(1,1)) |
279 |
IndZmat(2,1)=Order(IndZmat0(2,1)) |
280 |
IndZmat(2,2)=Order(IndZmat0(2,2)) |
281 |
IndZmat(3,1)=Order(IndZmat0(3,1)) |
282 |
IndZmat(3,2)=Order(IndZmat0(3,2)) |
283 |
IndZmat(3,3)=Order(IndZmat0(3,3)) |
284 |
DO I=4,Nat |
285 |
DO J=1,4 |
286 |
IndZmat(I,J)=Order(IndZmat0(I,J)) |
287 |
END DO |
288 |
end do |
289 |
IF (DEBUG) THEN |
290 |
WRITE(IOOUT,*) "DBG PathCreate : IndZmat" |
291 |
DO I=1,Nat |
292 |
WRITE(IOOUT,*) (IndZmat(I,J),J=1,5) |
293 |
END DO |
294 |
WRITE(IOOUT,*) "DBG PathCreate : IndZmat0" |
295 |
DO I=1,Nat |
296 |
WRITE(IOOUT,*) (IndZmat0(I,J),J=1,5) |
297 |
END DO |
298 |
|
299 |
END IF |
300 |
|
301 |
! It is the first call, we have to create all internal coordinates |
302 |
if (debug) WrITE(*,*) "DBG PathCreate L302: First Call, we generate internal coords" |
303 |
DO igeom=1,NgeomI |
304 |
x(1:Nat) = XyzGeomI(IGeom,1,1:Nat) |
305 |
y(1:Nat) = XyzGeomI(IGeom,2,1:Nat) |
306 |
z(1:Nat) = XyzGeomI(IGeom,3,1:Nat) |
307 |
|
308 |
if (debug) WRITE(*,*) "DBG PathCreate L308: we generate internal coords for geom",IGeom |
309 |
|
310 |
Call ConvXyzZmat(Nat,x,y,z,IndZmat0,val_zmatTmp) |
311 |
IntCoordI(IGeom,1)=val_zmatTmp(2,1) |
312 |
IntCoordI(IGeom,2)=val_zmatTmp(3,1) |
313 |
IntCoordI(IGeom,3)=val_zmatTmp(3,2)*Pi/180. |
314 |
Idx=4 |
315 |
DO i=4,nat |
316 |
IntCoordI(IGeom,Idx)=val_zmatTmp(i,1) |
317 |
Idx=Idx+1 |
318 |
IntCoordI(IGeom,Idx)=val_zmatTmp(i,2)*Pi/180. |
319 |
Idx=Idx+1 |
320 |
|
321 |
! Some tests to check that the dihedral angles are similar... this is |
322 |
! important if they are close to Pi. |
323 |
Delta=0. |
324 |
|
325 |
if (abs(val_zmatTMP(i,3)-val_zmat(i,3))>=180.) THEN |
326 |
if ((val_zmatTMP(i,3)-val_zmat(i,3))<=-180.) THEN |
327 |
Delta=-1.0d0*TwoPi |
328 |
ELSE |
329 |
Delta=TwoPi |
330 |
END IF |
331 |
if (debug) THEN |
332 |
WRITE(*,*) Nom(atome(i)), & |
333 |
abs(val_zmatTMP(i,3)-val_zmat(i,3)), & |
334 |
val_zmatTMP(i,3),val_zmat(i,3),Delta, & |
335 |
val_zmatTMP(i,3)-Delta |
336 |
END IF |
337 |
END IF |
338 |
IntCoordI(IGeom,Idx)=(val_zmatTmp(i,3)-Delta)/180.*Pi |
339 |
Idx=Idx+1 |
340 |
END DO |
341 |
END DO ! End Loop on Igeom |
342 |
|
343 |
CASE ('MIXED') |
344 |
! IN case we are using mixed coordinate system, we have to |
345 |
! we generate the internal coordinates with a Z-Matrix |
346 |
Renum=.TRUE. |
347 |
! |
348 |
call Calc_mixed_frag(Nat,atome,IndZmat0,val_zmat,x,y,z, & |
349 |
r_cov,fact,frozen,cart,ncart) |
350 |
|
351 |
if (debug) WRITE(*,*) 'Back from Calc_Mixed' |
352 |
|
353 |
! How to test this partial zmat ? it must be good as it was automatically generated... |
354 |
! IF (.NOT.test_zmat(nat,IndZmat0)) THEN |
355 |
! WRITE(IOOUT,*) "I cannot generate a valid Zmat... help" |
356 |
! STOP |
357 |
! END IF |
358 |
|
359 |
! The IndZmat0 generated by Calc_zmat refers to the order of the input x,y,z |
360 |
! However, we need it with the new order so that we can use the zmat |
361 |
! coordinates to generate cartesian coordinates. |
362 |
! So, we have to reorder it... |
363 |
DO I=1,Nat |
364 |
Order(IndZmat0(I,1))=I |
365 |
OrderInv(I)=IndZmat0(I,1) |
366 |
! I let X0 being the Cartesian coordinates of the reference geometry. Before it was |
367 |
! those of the First geometry (which was also the reference one). This might change! |
368 |
X0(i)=X(IndZmat0(i,1)) |
369 |
Y0(i)=Y(IndZmat0(i,1)) |
370 |
Z0(i)=Z(IndZmat0(i,1)) |
371 |
END DO |
372 |
IndZmat=0 |
373 |
IndZmat(1:NCart,:)=-1 |
374 |
|
375 |
DO I=1,Nat |
376 |
IndZmat(I,1)=Order(IndZmat0(I,1)) |
377 |
END DO |
378 |
|
379 |
SELECT CASE (NCart) |
380 |
CASE (1) |
381 |
IndZmat(2,2)=Order(IndZmat0(2,2)) |
382 |
IndZmat(3,2)=Order(IndZmat0(3,2)) |
383 |
IndZmat(3,3)=Order(IndZmat0(3,3)) |
384 |
IdX=4 |
385 |
CASE (2) |
386 |
IndZmat(3,2)=Order(IndZmat0(3,2)) |
387 |
IndZmat(3,3)=Order(IndZmat0(3,3)) |
388 |
Idx=4 |
389 |
CASE DEFAULT |
390 |
Idx=NCart+1 |
391 |
END SELECT |
392 |
|
393 |
DO I=Idx,Nat |
394 |
DO J=1,4 |
395 |
IndZmat(I,J)=Order(IndZmat0(I,J)) |
396 |
END DO |
397 |
end do |
398 |
IF (DEBUG) THEN |
399 |
WRITE(IOOUT,*) "DBG PathCreate : IndZmat - Mixed" |
400 |
DO I=1,Nat |
401 |
WRITE(IOOUT,*) (IndZmat(I,J),J=1,5) |
402 |
END DO |
403 |
END IF |
404 |
|
405 |
! It is the first call, we have to create all internal coordinates |
406 |
! Idx=1 |
407 |
! DO I=1,NCart |
408 |
! IntCoordI(1,Idx)=val_zmat(I,1) |
409 |
! IntCoordI(1,Idx+1)=val_zmat(I,2) |
410 |
! IntCoordI(1,Idx+2)=val_zmat(I,3) |
411 |
! Idx=Idx+3 |
412 |
! END DO |
413 |
! SELECT CASE (NCART) |
414 |
! CASE (1) |
415 |
! IntCoordI(1,Idx)=val_zmat(2,1) |
416 |
! IntCoordI(1,Idx+1)=val_zmat(3,1) |
417 |
! IntCoordI(1,Idx+2)=val_zmat(3,2)*Pi/180. |
418 |
! Idx=Idx+3 |
419 |
! IBeg=4 |
420 |
! CASE (2) |
421 |
! IntCoordI(1,Idx)=val_zmat(3,1) |
422 |
! IntCoordI(1,Idx+1)=val_zmat(3,2)*Pi/180. |
423 |
! Idx=Idx+2 |
424 |
! IBeg=4 |
425 |
! CASE DEFAULT |
426 |
! IBeg=NCart+1 |
427 |
! END SELECT |
428 |
! DO i=iBeg,Nat |
429 |
! IntCoordI(1,Idx)=val_zmat(i,1) |
430 |
! Idx=Idx+1 |
431 |
! DO j=2,3 |
432 |
! IntCoordI(1,Idx)=val_zmat(i,j)*Pi/180. |
433 |
! Idx=Idx+1 |
434 |
! END DO |
435 |
! END DO |
436 |
|
437 |
! If (debug) WRITE(*,*) "Idx, NCoord",Idx-1,NCoord |
438 |
|
439 |
DO Igeom=1,NgeomI |
440 |
x(1:Nat) = XyzGeomI(IGeom,1,1:Nat) |
441 |
y(1:Nat) = XyzGeomI(IGeom,2,1:Nat) |
442 |
z(1:Nat) = XyzGeomI(IGeom,3,1:Nat) |
443 |
|
444 |
Call ConvXyzMixed(Nat,Ncart,x,y,z,IndZmat0,val_zmatTmp(1,1)) |
445 |
Idx=1 |
446 |
DO I=1,NCart |
447 |
IntCoordI(IGeom,Idx)=val_zmatTmp(I,1) |
448 |
IntCoordI(IGeom,Idx+1)=val_zmatTmp(I,2) |
449 |
IntCoordI(IGeom,Idx+2)=val_zmatTmp(I,3) |
450 |
Idx=Idx+3 |
451 |
END DO |
452 |
|
453 |
SELECT CASE (NCART) |
454 |
CASE (1) |
455 |
IntCoordI(IGeom,Idx)=val_zmatTmp(2,1) |
456 |
Idx=Idx+1 |
457 |
IntCoordI(IGeom,Idx)=val_zmatTmp(3,1) |
458 |
IntCoordI(IGeom,Idx+1)=val_zmatTmp(3,2)*Pi/180. |
459 |
Idx=Idx+2 |
460 |
IBeg=4 |
461 |
CASE (2) |
462 |
IntCoordI(IGeom,Idx)=val_zmatTmp(3,1) |
463 |
IntCoordI(IGeom,Idx+1)=val_zmatTmp(3,2)*Pi/180. |
464 |
Idx=Idx+2 |
465 |
IBeg=4 |
466 |
CASE DEFAULT |
467 |
Ibeg=Ncart+1 |
468 |
END SELECT |
469 |
DO i=IBeg,Nat |
470 |
IntCoordI(IGeom,Idx)=val_zmatTmp(i,1) |
471 |
Idx=Idx+1 |
472 |
IntCoordI(IGeom,Idx)=val_zmatTmp(i,2)*Pi/180. |
473 |
Idx=Idx+1 |
474 |
|
475 |
! Some tests to check that the dihedral angles are similar... this is |
476 |
! important if they are close to Pi. |
477 |
Delta=0. |
478 |
|
479 |
if (abs(val_zmatTMP(i,3)-val_zmat(i,3))>=180.) THEN |
480 |
if ((val_zmatTMP(i,3)-val_zmat(i,3))<=-180.) THEN |
481 |
Delta=-1.0d0*TwoPi |
482 |
ELSE |
483 |
Delta=TwoPi |
484 |
END IF |
485 |
if (debug) THEN |
486 |
WRITE(*,*) Nom(atome(i)), & |
487 |
abs(val_zmatTMP(i,3)-val_zmat(i,3)), & |
488 |
val_zmatTMP(i,3),val_zmat(i,3),Delta, & |
489 |
val_zmatTMP(i,3)-Delta |
490 |
END IF |
491 |
END IF |
492 |
IntCoordI(IGeom,Idx)=(val_zmatTmp(i,3)-Delta)/180.*Pi |
493 |
Idx=Idx+1 |
494 |
END DO |
495 |
|
496 |
END DO |
497 |
CASE ('CART') |
498 |
DO I=1,Nat |
499 |
Order(I)=I |
500 |
OrderInv(I)=I |
501 |
END DO |
502 |
X0=X |
503 |
Y0=y |
504 |
Z0=z |
505 |
END SELECT |
506 |
|
507 |
ELSE ! First iteration of the optimization. Match at L616 |
508 |
|
509 |
IGeom=1 |
510 |
x(1:Nat) = XyzGeomI(IGeom,1,1:Nat) |
511 |
y(1:Nat) = XyzGeomI(IGeom,2,1:Nat) |
512 |
z(1:Nat) = XyzGeomI(IGeom,3,1:Nat) |
513 |
|
514 |
SELECT CASE (COORD) |
515 |
CASE ('HYBRID') |
516 |
IndZmat0=IndZmat |
517 |
Call ConvXyzZmat(Nat,x,y,z,IndZmat,val_zmat(1,1)) |
518 |
CASE ('ZMAT') |
519 |
IndZmat0=IndZmat |
520 |
val_zmat=0.d0 |
521 |
val_zmat(2,1)=IntCoordI(1,1) |
522 |
val_zmat(3,1)=IntCoordI(1,2) |
523 |
val_zmat(3,2)=IntCoordI(1,3)*180./Pi |
524 |
|
525 |
Idx=4 |
526 |
DO iat=4,Nat |
527 |
val_zmat(iat,1)=IntCoordI(1,idx) |
528 |
Idx=Idx+1 |
529 |
do j=2,3 |
530 |
val_zmat(iat,J)=IntCoordI(1,idx)*180./Pi |
531 |
Idx=Idx+1 |
532 |
END DO |
533 |
END DO |
534 |
|
535 |
CASE ('MIXED') |
536 |
IndZmat0=IndZmat |
537 |
val_zmat=0.d0 |
538 |
Idx=1 |
539 |
DO I=1,NCart |
540 |
DO J=1,3 |
541 |
val_zmat(i,j)= IntCoordI(1,Idx) |
542 |
Idx=Idx+1 |
543 |
END DO |
544 |
END DO |
545 |
SELECT CASE (NCart) |
546 |
CASE(1) |
547 |
val_zmat(2,1)=IntCoordI(1,Idx) |
548 |
val_zmat(3,1)=IntCoordI(1,Idx+1) |
549 |
val_zmat(3,2)=IntCoordI(1,Idx+2)*180./Pi |
550 |
Idx=Idx+3 |
551 |
IBeg=4 |
552 |
CASE(2) |
553 |
val_zmat(3,1)=IntCoordI(1,Idx) |
554 |
val_zmat(3,2)=IntCoordI(1,Idx)*180./Pi |
555 |
Idx=Idx+2 |
556 |
IBeg=4 |
557 |
CASE DEFAULT |
558 |
IBeg=NCart+1 |
559 |
END SELECT |
560 |
|
561 |
DO Iat=IBeg,Nat |
562 |
val_zmat(iat,1)=IntCoordI(1,idx) |
563 |
Idx=Idx+1 |
564 |
do j=2,3 |
565 |
val_zmat(iat,J)=IntCoordI(1,idx)*180./Pi |
566 |
Idx=Idx+1 |
567 |
END DO |
568 |
END DO |
569 |
CASE ('BAKER') |
570 |
! Nothing to be done here. |
571 |
CASE ('CART') |
572 |
! Nothing to be done here. |
573 |
CASE DEFAULT |
574 |
WRITE(*,*) "Coord=",TRIM(COORD)," not recognized in PathCreate.L554.STOP" |
575 |
STOP |
576 |
END SELECT |
577 |
X0=x |
578 |
y0=y |
579 |
z0=z |
580 |
END IF ! First |
581 |
|
582 |
! Now that we have a zmat, we will generate all the IntCoodI corresponding... |
583 |
! First one |
584 |
IF (COORD.EQ.'HYBRID') THEN ! Matches at L680 |
585 |
DO IGeom=1,NGeomI |
586 |
x(1:Nat) = XyzGeomI(IGeom,1,1:Nat) |
587 |
y(1:Nat) = XyzGeomI(IGeom,2,1:Nat) |
588 |
z(1:Nat) = XyzGeomI(IGeom,3,1:Nat) |
589 |
|
590 |
Call ConvXyzZmat(Nat,x,y,z,IndZmat0,val_zmatTmp(1,1)) |
591 |
IntCoordI(IGeom,1)=val_zmatTmp(2,1) |
592 |
IntCoordI(IGeom,2)=val_zmatTmp(3,1) |
593 |
IntCoordI(IGeom,3)=val_zmatTmp(3,2)*Pi/180. |
594 |
Idx=4 |
595 |
DO i=4,nat |
596 |
IntCoordI(IGeom,Idx)=val_zmatTmp(i,1) |
597 |
Idx=Idx+1 |
598 |
IntCoordI(IGeom,Idx)=val_zmatTmp(i,2)*Pi/180. |
599 |
Idx=Idx+1 |
600 |
|
601 |
! Some tests to check that the dihedral angles are similar... this is |
602 |
! important if they are close to Pi. |
603 |
Delta=0. |
604 |
|
605 |
if (abs(val_zmatTMP(i,3)-val_zmat(i,3))>=180.) THEN |
606 |
if ((val_zmatTMP(i,3)-val_zmat(i,3))<=-180.) THEN |
607 |
Delta=-1.0d0*TwoPi |
608 |
ELSE |
609 |
Delta=TwoPi |
610 |
END IF |
611 |
if (debug) THEN |
612 |
WRITE(*,*) Nom(atome(i)), & |
613 |
abs(val_zmatTMP(i,3)-val_zmat(i,3)), & |
614 |
val_zmatTMP(i,3),val_zmat(i,3),Delta, & |
615 |
val_zmatTMP(i,3)-Delta |
616 |
END IF |
617 |
END IF |
618 |
IntCoordI(IGeom,Idx)=(val_zmatTmp(i,3)-Delta)/180.*Pi |
619 |
Idx=Idx+1 |
620 |
END DO |
621 |
END DO |
622 |
END IF ! Matches Coord=Hybrid |
623 |
|
624 |
! PFL 24 Nov 2008 -> |
625 |
! This should not be necessary... |
626 |
! ! if we have frozen atoms, we make sure that they do not move between geometries |
627 |
! IF (IntFroz.NE.0) THEN |
628 |
! if (debug) WRITE(*,*) 'DBG PathCreate L641: Number of frozen coordinates=', IntFroz |
629 |
! DO IGeom=2,NGeomI ! For IOpt .GT. 0, NGeomI is equal to NGeomF |
630 |
! IntCoordI(IGeom,1:IntFroz)=IntCoordI(1,1:IntFroz) |
631 |
! END DO |
632 |
! END IF |
633 |
! -> PFL 24 Nov 2008 |
634 |
|
635 |
Idx=min(9,NCoord) |
636 |
|
637 |
IF (DEBUG.AND.(COORD.NE.'CART')) THEN |
638 |
WRITE(*,*) "DBG PathCreate. L685 IntCoordI(IGeom,:)" |
639 |
DO I=1,NGeomI |
640 |
WRITE(*,'("Geom:",I5,9(1X,F10.4))') I,IntCoordI(I,1:Idx) |
641 |
END DO |
642 |
! We write it also in terms of Zmat |
643 |
IF ((COORD.EQ.'ZMAT').OR.(COORD.EQ.'HYBRID')) THEN |
644 |
DO I=1,NGeomI |
645 |
WRITE(*,*) 'Zmat for geom ',I,'/',NGeomI,'Xgeom=',Xgeom(I) |
646 |
WRITE(*,'(1X,A5,3(1X,I5,1X,F11.6))') Nom(Atome(IndZmat0(1,1))) |
647 |
WRITE(*,'(1X,A5,3(1X,I5,1X,F11.6))') Nom(Atome(IndZmat0(2,1))), & |
648 |
IndZmat(2,2),IntCoordI(I,1) |
649 |
WRITE(*,'(1X,A5,3(1X,I5,1X,F11.6))') Nom(Atome(IndZmat0(3,1))), & |
650 |
IndZmat(3,2),IntCoordI(I,2),IndZmat(3,3),IntCoordI(I,3)*180./Pi |
651 |
Idx=4 |
652 |
DO J=4,Nat |
653 |
WRITE(*,'(1X,A5,3(1X,I5,1X,F11.6))') Nom(Atome(IndZmat0(J,1))), & |
654 |
IndZmat(J,2),IntCoordI(I,Idx),IndZmat(J,3), & |
655 |
IntCoordI(I,Idx+1)*180./Pi, & |
656 |
IndZmat(J,4),IntCoordI(I,Idx+2)*180./Pi |
657 |
Idx=Idx+3 |
658 |
END DO |
659 |
|
660 |
XyzTmp2=0. |
661 |
! We convert it into Cartesian coordinates |
662 |
XyzTmp2(2,1)=IntCoordI(I,1) |
663 |
d=IntCoordI(I,2) |
664 |
a_val=IntCoordI(I,3) |
665 |
if (Nat.GE.3) THEN |
666 |
if (IndZmat(3,2).EQ.1) THEN |
667 |
XyzTmp2(3,1)=XYzTmp2(1,1)+d*cos(a_val) |
668 |
ELSE |
669 |
XyzTmp2(3,1)=XyzTmp2(2,1)-d*cos(a_val) |
670 |
ENDIF |
671 |
XyzTmp2(3,2)=d*sin(a_val) |
672 |
ENDIF |
673 |
|
674 |
Idx=4 |
675 |
DO iat=4,Nat |
676 |
val_zmatTMP(iat,1)=IntCoordI(I,idx) |
677 |
Idx=Idx+1 |
678 |
DO j=2,3 |
679 |
val_zmatTMP(iat,J)=IntCoordI(I,idx)*180./Pi |
680 |
Idx=Idx+1 |
681 |
END DO |
682 |
END DO |
683 |
DO iat=4,Nat |
684 |
call ConvertZmat_cart(iat,IndZmat,val_zmatTMP, & |
685 |
XYzTMP2(1,1), XYzTMP2(1,2),XYzTMP2(1,3)) |
686 |
END DO |
687 |
DO Iat=1,nat |
688 |
WRITE(*,'(1X,A5,3(1X,F11.6))') Nom(Atome(IndZmat0(Iat,1))),& |
689 |
XyzTmp2(iat,1:3) |
690 |
END DO |
691 |
|
692 |
END DO |
693 |
END IF |
694 |
IF (COORD.EQ.'MIXED') THEN |
695 |
DO I=1,NGeomI |
696 |
WRITE(*,*) 'Cart+Zmat for geom ',I,'/',NGeomI,'Xgeom=',Xgeom(I) |
697 |
Idx=1 |
698 |
XyzTmp2=0. |
699 |
DO J=1,NCART |
700 |
WRITE(*,'(1X,A5,3(1X,F11.6))') Nom(Atome(IndZmat0(1,1))), & |
701 |
IntCoordI(I,Idx:Idx+2) |
702 |
XyzTmp2(J,1:3)=IntCoordI(I,Idx:Idx+2) |
703 |
Idx=Idx+3 |
704 |
END DO |
705 |
SELECT CASE (NCart) |
706 |
CASE (1) |
707 |
J=2 |
708 |
WRITE(*,'(1X,A5,3(I5,F11.6))') Nom(Atome(IndZmat0(J,1))), & |
709 |
IndZmat(J,2),IntCoordI(I,Idx) |
710 |
Idx=Idx+1 |
711 |
J=3 |
712 |
WRITE(*,'(1X,A5,3(I5,F11.6))') Nom(Atome(IndZmat0(J,1))), & |
713 |
IndZmat(J,2),IntCoordI(I,Idx),IndZmat(J,3), & |
714 |
IntCoordI(I,Idx+1)*180./Pi |
715 |
Idx=Idx+2 |
716 |
Ibeg=4 |
717 |
CASE (2) |
718 |
J=3 |
719 |
WRITE(*,'(1X,A5,3(I5,F11.6))') Nom(Atome(IndZmat0(J,1))), & |
720 |
IndZmat(J,2),IntCoordI(I,Idx),IndZmat(J,3), & |
721 |
IntCoordI(I,Idx+1)*180./Pi |
722 |
Idx=Idx+2 |
723 |
Ibeg=4 |
724 |
CASE DEFAULT |
725 |
IBeg=NCart+1 |
726 |
END SELECT |
727 |
DO J=IBeg,Nat |
728 |
IF (J.EQ.2) & |
729 |
WRITE(*,'(1X,A5,3(I5,F11.6))') Nom(Atome(IndZmat0(J,1))), & |
730 |
IndZmat(J,2),IntCoordI(I,Idx),IndZmat(J,3), & |
731 |
IntCoordI(I,Idx+1)*180./Pi, & |
732 |
IndZmat(J,4),IntCoordI(I,Idx+2)*180./Pi |
733 |
Idx=Idx+3 |
734 |
END DO |
735 |
|
736 |
! We convert it into Cartesian coordinates |
737 |
IntCoordTmp=IntCoordI(I,1:NCoord) |
738 |
Call Mixed2cart(Nat,IndZmat,IntCoordTmp,XyzTmp2) |
739 |
|
740 |
DO Iat=1,nat |
741 |
WRITE(*,'(1X,A5,3(1X,F11.6))') Nom(Atome(IndZmat0(Iat,1))),& |
742 |
XyzTmp2(iat,1:3) |
743 |
END DO |
744 |
|
745 |
END DO |
746 |
END IF |
747 |
END IF ! matches IF (DEBUG.AND.(COORD.NE.'CART')) THEN |
748 |
|
749 |
if (debug) WRITE(*,*) "Before interpolation, PathCreate.f90, L740, IOpt=",IOpt, & |
750 |
"ISpline=", ISpline |
751 |
! Now comes the Interpolation: |
752 |
IF ((NGeomI>2).AND.(IOpt.GE.ISpline)) THEN |
753 |
Linear=.FALSE. |
754 |
! We have at least three geometries so we can apply cubic spline |
755 |
SELECT CASE (COORD) |
756 |
CASE ('ZMAT','HYBRID','MIXED') |
757 |
DO I=1,NCoord |
758 |
! We compute the spline coefficients |
759 |
call spline(xGeom,IntCoordI(1,I),NGeomI,Inf,Inf, Coef(1,I)) |
760 |
if (debug) THEN |
761 |
WRITE(*,*) 'Coef Spline for coord',I |
762 |
WRITE(*,*) Coef(1:NGeomI,I) |
763 |
END IF |
764 |
END DO |
765 |
CASE ('BAKER') |
766 |
! We compute the spline coefficients |
767 |
! xGeom(NGeomI), IntCoordI(NGeomI,3*Nat-6) declared in Path_module.f90 |
768 |
! can also be used for the Baker's internal coordinates. |
769 |
! we need to get Baker's internal coordinates from cartesian coordinates. |
770 |
! as we have subroutine ConvXyzmat(...) in Z matrix case. |
771 |
! Coef(NGeomI,NCoord) or (NGeomI,N3at) has INTENT(OUT) |
772 |
DO I=1,NCoord ! NCoord=3*Nat-6-symmetry_eliminated. |
773 |
call spline(xGeom,IntCoordI(1,I),NGeomI,Inf,Inf,Coef(1,I)) |
774 |
! IF (debug) THEN |
775 |
! WRITE(*,*) 'Coef Spline for coord',I |
776 |
! WRITE(*,*) Coef(1:NGeomI,I) |
777 |
! END IF |
778 |
END DO |
779 |
CASE ('CART') |
780 |
DO I=1,Nat |
781 |
! We compute the spline coefficients |
782 |
call spline(xGeom,XyzGeomI(1,1,I),NGeomI,Inf,Inf, Coef(1,3*I-2)) |
783 |
call spline(xGeom,XyzGeomI(1,2,I),NGeomI,Inf,Inf, Coef(1,3*I-1)) |
784 |
call spline(xGeom,XyzGeomI(1,3,I),NGeomI,Inf,Inf, Coef(1,3*I)) |
785 |
if (debug) THEN |
786 |
WRITE(*,*) 'Coef Spline for coord',i |
787 |
WRITE(*,*) Coef(1:NGeomI,I) |
788 |
END IF |
789 |
END DO |
790 |
CASE DEFAULT |
791 |
WRITE(*,*) "Coord=",TRIM(COORD)," not recognized in PathCreate.L783.STOP" |
792 |
STOP |
793 |
END SELECT |
794 |
ELSE ! matches IF ((NGeomI>2).AND.(Iopt.Ge.ISpline)) THEN |
795 |
! On n'a que deux images. On fera une interpolation lineaire, |
796 |
! qui est un cas particulier avec Coef=0 |
797 |
if (debug.AND.(NGeomI.EQ.2)) WRITE(*,*) "DBG : Only 2 starting geometries" |
798 |
if (debug.AND.(Iopt.LE.ISpline)) WRITE(*,*) "DBG : Not enough path -> linear int" |
799 |
Coef=0.d0 |
800 |
Linear=.TRUE. |
801 |
END IF ! matches IF ((NGeomI>2).AND.(Iopt.Ge.ISpline)) THEN |
802 |
! Shall we redistribute the points along the path ? |
803 |
if (debug) WRITE(*,*) "PathCreate.f90, L795, IOpt=", IOpt, "IReparam=", IReparam |
804 |
IF (MOD(IOpt,IReparam).EQ.0) THEN |
805 |
|
806 |
! We generate the Path, in two steps: |
807 |
! i) we calculate the length of the mass weighted (MW) path |
808 |
! ii) we sample the path to get the geometries |
809 |
|
810 |
NGeomS=NGeomI |
811 |
SELECT CASE (COORD) |
812 |
CASE ('ZMAT','HYBRID') |
813 |
! We call the extrapolation once to get the path length |
814 |
dist=Inf |
815 |
Call ExtraPol_int(IOpt,s,dist,x0,y0,z0,xgeom,Coef,XgeomF) |
816 |
! we have the length, we calculate the distance between two points |
817 |
|
818 |
if (s.LE.1e-6) THEN |
819 |
IF (OptGeom.LE.0) THEN |
820 |
WRITE(*,*) "Length of the path is 0 and you are not doing Geometry Optimization." |
821 |
WRITE(*,*) "ERROR !!! Stop !" |
822 |
STOP |
823 |
END IF |
824 |
ELSE |
825 |
! we have the length, we calculate the distance between two points |
826 |
dist=s/Real(NGeomf-1) |
827 |
if (debug) WRITE(*,*) 'Dbg PathCreate ZMAT s, dist:',s,dist |
828 |
! we call it again to obtain the geometries ! |
829 |
Call ExtraPol_int(iopt,s,dist,x0,y0,z0,xgeom,Coef,XgeomF) |
830 |
END IF |
831 |
CASE ('BAKER') |
832 |
! We generate the Path, in two steps: |
833 |
! i) we calculate the length of the mass weighted (MW) path |
834 |
! ii) we sample the path to get the geometries |
835 |
|
836 |
! We call the extrapolation first time to get the path length |
837 |
! iopt: Number of the cycles for the optimization. |
838 |
! s: a real number and has INTENT(OUT), probably returns the |
839 |
! length of the path. |
840 |
! dist=Inf=> ExtraPol_baker has to calculate the length of the path. |
841 |
! X0(Nat),Y0(Nat),Z0(Nat): reference geometry. |
842 |
! Xgeom: Xgeom(NGeomI) has INTENT(IN) |
843 |
! Coef(NGeomI,NCoord) is obtained from spline interpolation subroutine. |
844 |
! XgeomF: XGeomF(NGeomF) has INTENT(OUT) |
845 |
! Which reference coordinate geometry X0, Y0, Z0 to use??? |
846 |
dist=Inf |
847 |
!if (debug) WRITE(*,*) "Before the call of ExtraPol_baker in redistribution & |
848 |
!of the points, in PathCreate.f90, L836" |
849 |
!Print *, 'Before ExtraPol_baker, PathCreate.90, L848, IntCoordI=' |
850 |
!Print *, IntCoordI |
851 |
Call ExtraPol_baker(s,dist,x0,y0,z0,xgeom,Coef,XgeomF) |
852 |
!Print *, 'After ExtraPol_baker, PathCreate.90, L848, IntCoordI=' |
853 |
!Print *, IntCoordI |
854 |
!if (debug) WRITE(*,*) "After the call of ExtraPol_baker in the redistribution & |
855 |
! of the points, in PathCreate.f90, L843" |
856 |
|
857 |
! we have the lenght, we calculate the distance between two points |
858 |
!Print *, 'After first call of ExtraPol_baker in PathCreate.f90, s=', s |
859 |
|
860 |
if (s.LE.1e-6) THEN |
861 |
IF (OptGeom.LE.0) THEN |
862 |
WRITE(*,*) "Length of the path is 0 and you are not doing Geometry Optimization." |
863 |
WRITE(*,*) "ERROR !!! Stop !" |
864 |
STOP |
865 |
END IF |
866 |
ELSE |
867 |
|
868 |
dist=s/Real(NGeomf-1) |
869 |
!if (debug) WRITE(*,*) 'Dbg PathCreate ZMAT s, dist:',s,dist |
870 |
|
871 |
! we call it again to obtain the geometries ! |
872 |
Call ExtraPol_baker(s,dist,x0,y0,z0,xgeom,Coef,XgeomF) |
873 |
WRITE(*,*) "At the end of Baker case in the redistribution of the points, in PathCreate.f90, L966" |
874 |
END IF |
875 |
|
876 |
DO IGeom=1,NGeomF |
877 |
WRITE(*,*) "UMatF for IGeom=",IGeom |
878 |
DO I=1,3*Nat-6 |
879 |
WRITE(*,'(50(1X,F12.8))') UMatF(IGeom,:,I) |
880 |
END DO |
881 |
END DO |
882 |
|
883 |
CASE ('MIXED') |
884 |
! WRITE(*,*) "IOIOIOIOIOIOIOI" |
885 |
! We call the extrapolation once to get the path length |
886 |
Dist=Inf |
887 |
Call ExtraPol_Mixed(s,dist,x0,y0,z0,xgeom,Coef) |
888 |
|
889 |
if (s.LE.1e-6) THEN |
890 |
IF (OptGeom.LE.0) THEN |
891 |
WRITE(*,*) "Length of the path is 0 and you are not doing Geometry Optimization." |
892 |
WRITE(*,*) "ERROR !!! Stop !" |
893 |
STOP |
894 |
END IF |
895 |
ELSE |
896 |
|
897 |
! we have the length, we calculate the distance between two points |
898 |
dist=s/Real(NGeomf-1) |
899 |
if (debug) WRITE(*,*) 'Dbg PathCreate Mixed s, dist:',s,dist |
900 |
|
901 |
! we call it again to obtain the geometries ! |
902 |
Call ExtraPol_Mixed(s,dist,x0,y0,z0,xgeom,Coef) |
903 |
|
904 |
IF (debug) THEN |
905 |
DO I=1,NGeomF |
906 |
WRITE(*,'(1X,A,12(1X,F10.5))') "IntTangent:",IntTangent(I,1:NCoord) |
907 |
END DO |
908 |
END IF |
909 |
END IF |
910 |
CASE ('CART') |
911 |
! We call the extrapolation once to get the path length |
912 |
Dist=Inf |
913 |
Call ExtraPol_cart(iopt,s,dist,x0,y0,z0,xgeom,Coef) |
914 |
|
915 |
if (s.LE.1e-6) THEN |
916 |
IF (OptGeom.LE.0) THEN |
917 |
WRITE(*,*) "Length of the path is 0 and you are not doing Geometry Optimization." |
918 |
WRITE(*,*) "ERROR !!! Stop !" |
919 |
STOP |
920 |
END IF |
921 |
ELSE |
922 |
! we have the lenght, we calculate the distance between two points |
923 |
dist=s/Real(NGeomf-1) |
924 |
if (debug) WRITE(*,*) 'Debug s, dist:',s,dist |
925 |
|
926 |
! we call it again to obtain the geometries ! |
927 |
Call ExtraPol_cart(iopt,s,dist,x0,y0,z0,xgeom,Coef) |
928 |
END IF |
929 |
END SELECT |
930 |
ELSE |
931 |
! PFL 3 Jan 2008 -> |
932 |
! Tangents are not recalculated if the points are not reparameterized |
933 |
! PFL 6 Apr 2008 -> |
934 |
! Unless user has asked to reparameterized them ! |
935 |
IF (mod(Iopt,iReparamT).EQ.0) THEN |
936 |
XGeomF=XGeom |
937 |
NGeomS=NGeomI |
938 |
Call CalcTangent(XgeomF,NGeomS,xgeom,Coef) |
939 |
! |
940 |
END IF |
941 |
! <- PFL 3 Jan 2008 / 6 Apr 2008 |
942 |
END IF ! if (mod(Iop,iReparam).EQ.0) |
943 |
if (debug) WRITE(*,*) "PathCreate.f90, L885" |
944 |
|
945 |
! PFL 22.Nov.2007 -> |
946 |
! We do not write tangents for baker coordinates because they are hard to |
947 |
! interpret for a chemist. |
948 |
|
949 |
IF (debug.AND.(COORD.NE."BAKER")) THEN |
950 |
! we write the tangents :-) |
951 |
DO I=1,NGeomF |
952 |
SELECT CASE(Coord) |
953 |
CASE ('ZMAT','MIXED') |
954 |
IntCoordTmp=IntTangent(I,:) |
955 |
WRITE(*,'(1X,A,12(1X,F10.5))') "IntCoordTmp:",IntCoordTmp(1:NCoord) |
956 |
WRITE(*,'(1X,A,12(1X,F10.5))') "IntTangent:",IntTangent(I,1:NCoord) |
957 |
CASE ('CART','HYBRID') |
958 |
IntCoordTmp=XyzTangent(I,:) |
959 |
CASE DEFAULT |
960 |
WRITE(*,*) "Coord=",TRIM(COORD)," not recognized in PathCreate. STOP" |
961 |
STOP |
962 |
END SELECT |
963 |
WRITE(Title,"('Tangents for geometry ',I3,'/',I3,' for iteration ',I3)") I,NgeomF |
964 |
Call PrintGeom(Title,Nat,Ncoord,IntCoordTmp,Coord,6,Atome,Order,OrderInv,IndZmat) |
965 |
END DO |
966 |
END IF |
967 |
|
968 |
|
969 |
IF (DEBUG.AND.(COORD.NE.'CART')) THEN |
970 |
Idx=min(12,NCoord) |
971 |
WRITE(*,*) "DBG PathCreate. IntCoordF(IGeom,:)" |
972 |
DO I=1,NGeomF |
973 |
WRITE(*,'("Geom:",I5,12(1X,F10.4))') I,IntCoordF(I,1:Idx) |
974 |
END DO |
975 |
END IF |
976 |
|
977 |
DEALLOCATE(Coef,val_zmat,val_zmatTMP) |
978 |
DEALLOCATE(X0,Y0,Z0,Indzmat0) |
979 |
DEALLOCATE(X,Y,Z,Xgeom,XgeomF) |
980 |
DEALLOCATE(XyzTmp,XyzTmp2) |
981 |
|
982 |
if (debug) Call header("PathCreate over") |
983 |
|
984 |
END SUBROUTINE PathCreate |
985 |
|