Statistiques
| Révision :

root / src / PathCreate.f90

Historique | Voir | Annoter | Télécharger (40,87 ko)

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