Statistiques
| Révision :

root / src / CalcDist_cart.f90 @ 12

Historique | Voir | Annoter | Télécharger (13,61 ko)

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