Statistiques
| Révision :

root / src / PathCreate.f90 @ 10

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