Statistiques
| Révision :

root / src / EgradPath.f90

Historique | Voir | Annoter | Télécharger (30,58 ko)

1
SUBROUTINE EGradPath(Iopt)
2

    
3
  ! This subroutine calculates the energy+gradient for all points of
4
  ! the path
5

    
6
!----------------------------------------------------------------------
7
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
8
!  Centre National de la Recherche Scientifique,
9
!  Université Claude Bernard Lyon 1. All rights reserved.
10
!
11
!  This work is registered with the Agency for the Protection of Programs 
12
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
13
!
14
!  Authors: P. Fleurat-Lessard, P. Dayal
15
!  Contact: optnpath@gmail.com
16
!
17
! This file is part of "Opt'n Path".
18
!
19
!  "Opt'n Path" is free software: you can redistribute it and/or modify
20
!  it under the terms of the GNU Affero General Public License as
21
!  published by the Free Software Foundation, either version 3 of the License,
22
!  or (at your option) any later version.
23
!
24
!  "Opt'n Path" is distributed in the hope that it will be useful,
25
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
26
!
27
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
28
!  GNU Affero General Public License for more details.
29
!
30
!  You should have received a copy of the GNU Affero General Public License
31
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
32
!
33
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
34
! for commercial licensing opportunities.
35
!----------------------------------------------------------------------
36

    
37
  use Path_module, only : ProgExe, NCoord, PROG, Nat, NGeomF, Coord, IntCoordF, &
38
       IndZmat, XyzGeomF, Atome, Order, OrderInv, Latr, FrozAtoms, &
39
       Grad, Energies, renum, dzdc, massat, Pi, NCART, OptReac, &
40
       OptProd,  AtName, Unit, CalcEReac, CalcEProd
41
  ! GeomOld_all(NGeomF,NCoord), BTransInv (3*Nat,NCoord): used for Baker case
42
  use Io_module
43

    
44
  IMPLICIT NONE
45

    
46
  INTEGER(KINT), INTENT(IN) :: Iopt
47

    
48
  INTEGER(KINT) :: IGeom,IGeom0,IGeomF
49
  CHARACTER(LCHARS) :: Line,FileInp,RunCommand
50
  CHARACTER(SCHARS) :: Line2
51

    
52
  REAL(KREAL), ALLOCATABLE :: GeomTmp(:),GradTmp(:) ! NCoord
53
  REAL(KREAL), ALLOCATABLE :: GradCart(:) ! 3*Nat
54
  REAL(KREAL), ALLOCATABLE :: PathCart(:,:) ! (3*Nat,NGeomF)
55
  REAL(KREAL), ALLOCATABLE :: x(:), y(:), z(:)
56
  REAL(KREAL), ALLOCATABLE :: x_k(:), y_k(:), z_k(:)
57
  REAL(KREAL), ALLOCATABLE :: GeomCart(:,:) !(Nat,3)
58
  REAL(KREAL) :: E
59
! Flag to see if we should print debug info
60
  LOGICAL :: Debug
61
! Flags to check if we have found the information we need
62
  LOGICAL, SAVE :: FReadE, FReadGrad
63
  LOGICAL, SAVE :: First=.TRUE.
64
! Flag to check if a file/directory exists
65
  LOGICAL :: FExists
66

    
67
  INTEGER(KINT) :: I, Iat, IBeg, Idx
68
  REAL(KREAL) :: RTmp1, RTmp2, RTmp3
69
  INTEGER(KINT) :: Itmp1, ITmp2
70

    
71
  INTERFACE
72
     function valid(string) result (isValid)
73
       CHARACTER(*), intent(in) :: string
74
       logical                  :: isValid
75
     END function VALID
76

    
77
     subroutine Egrad(E,Geom,Grad,NCoord,IGeom,IOpt,GeomCart,FOptGeom,GeomOld,GeomCart_old)
78

    
79
  ! This routines calculates the energy E and the gradient Grad of 
80
  ! a molecule with Geometry Geom (may be in internal coordinates),
81
  ! using for now, either Gaussian or Ext, more general later.
82

    
83
  use Path_module, only : Nat,AtName,Coord,dzdc,indzmat,Nom,Atome,massat,unit, &
84
       prog,NCart,XyzGeomF,IntCoordF,BTransInv, XyzGeomI, &
85
       GeomOld_all,BTransInvF,BTransInv_local,UMatF,UMat_local &
86
       , BprimT,a0,ScanCoord, Coordinate,NPrim,BMat_BakerT,BBT,BBT_inv &
87
      , Order,OrderInv, XPrimitiveF
88

    
89
  ! IntCoordF(NGeomF,NCoord),GeomOld_all(NGeomF,NCoord)
90
  ! allocated in Path.f90
91

    
92
  use Io_module
93

    
94
  ! Energy (calculated if F300K=.F., else estimated)
95
  REAL(KREAL), INTENT (OUT) :: E
96
  ! NCoord: Number of the degrees of freedom
97
  ! IGeom: index of the geometry.
98
  INTEGER(KINT), INTENT (IN) :: NCoord, IGeom, IOpt
99
  ! Geometry at which gradient is calculated (cf Factual also):
100
  REAL(KREAL), INTENT (INOUT) :: Geom(NCoord)
101
  ! Gradient calculated at Geom geometry:
102
  REAL(KREAL), INTENT (OUT) :: Grad(NCoord)
103
  ! Cartesian geometry corresponding to (Internal Geometry) Geom:
104
  REAL(KREAL), INTENT (OUT) :: GeomCart(Nat,3)
105
!!! Optional, just for geometry optimization with Baker coordinates
106
  REAL(KREAL), INTENT (IN), OPTIONAL :: GeomCart_old(Nat,3)
107
  REAL(KREAL), INTENT (INOUT), OPTIONAL :: GeomOld(NCoord)
108
! FOptGeom is a flag indicating if we are doing a geom optimization
109
! it can be omitted so that we use a local flag: Flag_Opt_Geom
110
  LOGICAL,INTENT (IN), OPTIONAL :: FOptGeom
111
! if FOptGeom is given Flag_Opt_Geom=FOptGeom, else Flag_Opt_Geom=F
112
  LOGICAL  :: Flag_Opt_Geom
113

    
114
 END subroutine Egrad
115

    
116
  END INTERFACE
117

    
118
  debug=valid('EGradPath')
119

    
120
  if (debug) Call header("Entering EgradPath")
121

    
122
  ALLOCATE(GeomTmp(NCoord))
123
  ALLOCATE(x(Nat),y(Nat),z(Nat))
124
  ALLOCATE(x_k(Nat),y_k(Nat),z_k(Nat))
125

    
126

    
127
  IF (RunMode=="PARA") THEN ! matches at L315
128

    
129
     ALLOCATE(GradCart(3*Nat),PathCart(3*Nat,NGeomF))
130

    
131

    
132
     SELECT CASE(Prog)
133
     CASE ("VASP")
134
        ! We will use the NEB routine of VASP to get all forces at once on Para8 queue
135

    
136
        ! First, we create all the POSCAR into the 0x directories
137

    
138
        WRITE(IOOUT,*) " Creating the POSCAR files "
139

    
140

    
141
        ! With RunMode="Para" one cannot optimize reactants or products (due to Vasp constraints)
142
        ! so this has been done beforehand :-)
143

    
144

    
145
        IGeom0=2
146
        IGeomF=NGeomF-1
147
        PathCart=0.d0
148

    
149
        IF (First) THEN
150
           ! For the first iteration, we do write a POSCAR into 00 and 0Final
151
           ! Vasp needs it !
152
           First=.FALSE.
153
           IGeom0=1
154
           IGeomF=NGeomF
155
! PFL 2013 OCt ->
156
! We might have to create the directories
157
           Line2="00"
158
           DO IGeom=IGeom0,IGeomF
159
              WRITE(Line,'(I5)') IGeom-1
160
              Idx=2-Len_TRIM(ADJUSTL(Line))
161
              FileInp=Line2(1:Idx) // TRIM(AdjustL(Line))
162
              INQUIRE(File=FileInp,Exist=FExists)
163
              If (.NOT.Fexists) THEN
164
                 FileInp="mkdir " // TRIM(FileInp)
165
                 if (debug) WRITE(*,'(1X,A)') "Creating dir: " // TRIM(FileInp)
166
                 CALL SYSTEM(FileInp)
167
              ELSE IF (DEBUG) THEN
168
                 WRITE(*,'(1X,A)') "Directory " // TRIM(FileInp) // " already exists"
169
              END IF
170
           END DO
171
        END IF   ! If (First)
172

    
173
        Line2="00"
174
        DO IGeom=IGeom0,IGeomF
175

    
176
           ! NOTE THAT HERE IGeom0 (IGeomF) IS NOT 1 (NGeomF) FOR NON-FIRST OPTIMIZATION.
177
           ! THIS WILL HAVE EFFECT ON XyzGeomF UPDATE IN BAKER CASE.
178
           WRITE(Line,'(I5)') IGeom-1
179
           Idx=2-Len_TRIM(ADJUSTL(Line))
180
           FileInp="." // FileDelim // Line2(1:Idx) // TRIM(AdjustL(Line)) // FileDelim // "POSCAR"
181
           if (debug) WRITE(*,*) "Creating ",TRIM(FileInp)
182
           OPEN(IOTMP,File=TRIM(FileInp))
183

    
184
           WRITE(Line,"('Geometry ',I3,'/',I3,' for iteration ',I3)") Igeom,NgeomF,Iopt
185
           if (debug) WRITE(*,*) Line
186
           SELECT CASE(Coord)
187
           CASE ('ZMAT')
188
              GeomTmp=IntCoordF(IGeom,:)
189
              Call Int2cart(nat,indzmat,geomTmp,PathCart(1,IGeom))
190
           CASE ('BAKER')
191
              GeomTmp=IntCoordF(IGeom,:)
192
              !
193
              IF (IOpt .EQ. 0) THEN
194
                 ! EgradPath(...) is called only after the call of PathCreate(...)
195
                 ! and in PathCreate, IF (MOD(IOpt,IReparam).EQ.0) (which is always 
196
                 ! true if IOpt==0), THEN ExtraPol_baker(...) is called.
197
                 ! In ExtraPol_baker(...), XyzGeomF(...) is calculated upon converting
198
                 ! the interpolated internal coordinates into cartesian coordinates.
199
                 ! Thus here we don't need to reconvert the internal coordinates again
200
                 ! to the cartesian coordinates. 
201
                 DO I=1,Nat
202
                    PathCart(3*I-2,IGeom) = XyzGeomF(IGeom,1,I)
203
                    PathCart(3*I-1,IGeom) = XyzGeomF(IGeom,2,I)
204
                    PathCart(3*I,IGeom) = XyzGeomF(IGeom,3,I)
205
                 END DO
206
              ELSE
207
                 ! XyzGeomF(NGeomF,3,Nat).
208
                 x_k(:) = XyzGeomF(IGeom,1,:)
209
                 y_k(:) = XyzGeomF(IGeom,2,:)
210
                 z_k(:) = XyzGeomF(IGeom,3,:)
211

    
212
                 !Call ConvertBakerInternal_cart(GeomOld_all(IGeom,:),IntCoordI(IGeom,:), &
213
                 !                               x_k,y_k,z_k,x,y,z)
214
                 ! PathCart(3*Nat,NGeomF)
215
                 DO I=1,Nat
216
                    PathCart(3*I-2,IGeom) = x(I)
217
                    PathCart(3*I-1,IGeom) = y(I)
218
                    PathCart(3*I,IGeom) = z(I)
219
                 END DO
220

    
221
                 XyzGeomF(IGeom,1,:)=x(:)
222
                 XyzGeomF(IGeom,2,:)=y(:)
223
                 XyzGeomF(IGeom,3,:)=z(:)
224
              END IF
225
           CASE ('MIXED')
226
              GeomTmp=IntCoordF(IGeom,:)
227
              Call Mixed2cart(nat,indzmat,geomTmp,PathCart(1,IGeom))
228
           CASE ('CART','HYBRID')
229
!!! CAUTION : PFL 29.AUG.2008 ->
230
              ! XyzGeomI/F stored in (NGeomI/F,3,Nat) and NOT (NGeomI/F,Nat,3)
231
              ! This should be made  consistent !!!!!!!!!!!!!!!
232
              GeomTmp=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/))
233
!!! <- CAUTION : PFL 29.AUG.2008 
234
            PathCart(:,IGeom)=GeomTmp
235
          CASE DEFAULT
236
            WRITE(*,*) "Coord=",TRIM(Coord)," not recognized. EgradPath L134. STOP"
237
            STOP
238
        END SELECT
239

    
240
           IF (debug) THEN
241
              WRITE(*,*) "Calling PrintGeomVasp for geom",Igeom
242
              Call PrintGeom(Line,Nat,NCoord,PathCart(1,Igeom),Coord,IoOut,Atome,Order,OrderInv,IndZmat)
243
           END IF
244
           Call PrintGeomVasp(Line,PathCart(1,IGeom),Latr,FrozAtoms,IoTmp)
245

    
246
           !           IF (debug) THEN 
247
           !              WRITE(*,*) 'DBG MAin, COORD=',TRIM(COORD), ' Igeom=',IGeom
248
           !              WRITE(*,'(3(1X,F9.4))') Reshape(Reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/))
249
           !              WRITE(*,'(3(1X,F9.4))') Reshape(XyzGeomF(IGeom,:,:),(/3*Nat/))
250
           !              DO Iat=1,Nat
251
           !                 WRITE(*,*) XyzGeomF(IGeom,1:3,Iat)
252
           !              END DO
253
           !           END IF
254

    
255
           IF (debug) THEN 
256
              WRITE(*,*) 'DBG MAin, COORD=',TRIM(COORD),' Igeom=',IGeom,' Iopt=',Iopt
257
              WRITE(*,*) GeomTmp(1:min(NCoord,9))
258
           END IF
259

    
260
           CLOSE(IOTMP)
261
        END DO ! matches DO IGeom=IGeom0,IGeomF
262

    
263
!!!!!!!!!!!!!!!!!!!
264
!
265
        ! We calculate the energies and gradients
266
!
267

    
268
        RunCommand=Trim(ProgExe)
269
        if (debug) WRITE(*,*) "Launching:", TRIM(RunCommand)
270
        WRITE(IOOUT,*) " Launching VASP to get the Forces "
271
        call system(RunCommand)
272
        if (debug) WRITE(*,*) "Back from:", TRIM(RunCommand)
273

    
274
!!!!!!!!!!!!!
275
!
276
        ! We read the gradients and energies
277
!
278
        WRITE(IOOUT,*) " Reading Forces "
279

    
280
        IGeom0=2
281
        IGeomF=NGeomF-1
282
        Grad=0.d0
283

    
284
        Line2="00"
285
        DO IGeom=IGeom0,IGeomF
286
           WRITE(Line,'(I5)') IGeom-1
287
           Idx=2-Len_TRIM(ADJUSTL(Line))
288
           FileInp="." // FileDelim // Line2(1:Idx) // TRIM(AdjustL(Line)) // FileDelim // "OUTCAR"
289
           if (debug) WRITE(*,*) "Reading E and forces from ", TRIM(FileInp)
290
           OPEN(IOTMP,File=TRIM(FileInp))
291

    
292
           ! We first search for the forces
293
           READ(IOTMP,'(A)',END=999,ERR=999) LINE
294
           ! We search for the  last part of the OUTCAR file, after wavefunction is converged
295
           DO WHILE (INDEX(LINE,'EDIFF is reached')==0)
296
              READ(IOTMP,'(A)',END=999,ERR=9991) LINE
297
           END DO
298

    
299
! PFL oct 2013 ->
300
! The order of the things that we search might change
301
! so that we look for TOTEN and TOTAL-FORCE in parallel :)
302
           FReadE=.FALSE.
303
           FReadGrad=.FALSE.
304
           DO WHILE (.NOT.(FReadE.AND.FReadGrad))
305
              READ(IOTMP,'(A)',END=999,ERR=9992) LINE
306

    
307
              IF (INDEX(LINE,'TOTEN')>0) THEN
308
                 Line=Line(26:)
309
                 READ(LINE,*) E
310
                 if (debug) WRITE(*,'(1X,A,I5,A,F20.6)') "DBG Egrad_VASP E(",Igeom,")=",E
311
                 Energies(Igeom)=E
312
                 FReadE=.TRUE.
313
              END IF
314

    
315
              IF (INDEX(LINE,'TOTAL-FORCE')>0) THEN
316
                 READ(IOTMP,'(A)',END=999,ERR=9993) LINE
317
                 DO I=1,Nat
318
                    Iat=I
319
                    IF (renum) Iat=Order(I)
320
                    READ(IOTMP,*,END=999,ERR=9994)  Rtmp1,RTmp2,RTmp3,GradCart(3*Iat-2:3*Iat)
321
                 END DO
322
                 FReadGrad=.TRUE.
323
              END IF
324
           END DO
325

    
326
           Close(IoTmp)
327

    
328
           WRITE(IOOUT,*) " Forces read for geometry ",IGeom
329

    
330
           IF (debug) THEN
331
              WRITE(*,*) "DBG EGRAD_VASP - GradCart=FORCES - original order"
332
              DO I=1,Nat
333
                 Iat=Order(I)
334
                 WRITE(*,'(1X,I5,3(1X,F20.6))') I,GradCart(3*Iat-2:3*Iat)
335
              END DO
336
              WRITE(*,*) "DBG EGRAD_VASP - GradCart=FORCES - internal order"
337
              DO I=1,Nat
338
                 Iat=Order(I)
339
                 WRITE(*,'(3(1X,I5),3(1X,F20.6))') I,Iat,OrderInv(I),GradCart(3*I-2:3*I)
340
              END DO
341
           END IF
342

    
343
           ! VASP gives the Forces in eV/Angstrom, so we convert it into the
344
           ! gradient in ua/Angstrom
345
           GradCart=-1.0d0*ev2Au*GradCart
346

    
347
           
348
           ! We convert it into the right coordinate system
349
           ! This should be put into a subroutine (because it is also in egradient)
350
           SELECT CASE (COORD)
351
           CASE ("ZMAT")
352
              ALLOCATE(GradTmp(3*Nat))
353
              if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_int"
354
              CALL CalcBmat_int(nat, PathCart(1:3*Nat,Igeom), indzmat, dzdc, massat,atome)
355
              CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp)
356

    
357
              Grad(IGeom,1)=GradTmp(4)
358
              Grad(IGeom,2)=GradTmp(7)
359
              ! We might have troubles whith angles that are not in the [0:pi] range because,
360
              ! when converted to catesian coord, they do appear in the [0:Pi] range to gaussian...
361
              ! so that the derivative is not good, and a multiplicative factor should be added...
362
              !
363
              ! This in fact should be taken care of in calc Bmat ...
364
              !
365
              IF ((IntCoordF(Igeom,3).LE.0).OR.(IntCoordF(Igeom,3).GE.Pi)) THEN
366
                 Grad(IGeom,3)=-1.0d0*GradTmp(8)
367
              ELSE
368
                 Grad(IGeom,3)=GradTmp(8)
369
              END IF
370
              Idx=4
371
              DO I=4,Nat
372
                 Grad(IGeom,Idx)=GradTmp(3*i-2)
373
                 Grad(IGeom,Idx+1)=GradTmp(3*i-1)
374
                 Grad(IGeom,Idx+2)=GradTmp(3*i)
375
                 Idx=Idx+3
376
              END DO
377
              DEALLOCATE(GradTmp)
378
              ! We have the gradient in Cartesian coordinates... which is ok for COORD=Cart, Hybrid
379
              ! but we have to convert it into internal coordinates if COORD=Baker      
380
           CASE ('BAKER')
381
              ALLOCATE(GradTmp(3*Nat))
382
              GradTmp=0.d0
383
              ! Below is to be corrected.
384
              ! This is inside 'IF ((PROG=="VASP").AND.(RunMode=="PARA")) THEN'
385
              !DO I=1, 3*Nat
386
              ! here GradTmp and Grad are gradients in Baker coordinates
387
              ! Not implemented  IF ((PROG=="VASP").AND.(RunMode=="PARA"))
388
              ! GradTmp(:) = GradTmp(:) + BTransInv(:,I)*GradCart(I)
389
              !END DO
390
              Grad(IGeom,:) = GradTmp
391
              DEALLOCATE(GradTmp)
392
           CASE ('MIXED')
393
              ALLOCATE(GradTmp(3*Nat))
394
              if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_mixed"
395
              CALL CalcBMat_mixed (nat,PathCart(1:3*Nat,IGeom), indzmat, dzdc, massat,atome)
396
              CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp)
397
              DO I=1,Nat
398
                 WRITE(*,'(1X,3(1X,F10.5))') GradTmp(3*I-2:3*I)
399
              END DO
400
              SELECT CASE (NCART)
401
              CASE (1)
402
                 Grad(IGeom,1:3)=GradTmp(1:3)
403
                 Grad(IGeom,4)=GradTmp(4)
404
                 Grad(IGeom,5)=GradTmp(7)
405
                 Grad(IGeom,6)=GradTmp(8)
406
                 Idx=7
407
                 IBeg=4
408
              CASE(2)
409
                 Grad(IGeom,1:3)=GradTmp(1:3)
410
                 Grad(IGeom,4:6)=GradTmp(4:6)
411
                 Grad(IGeom,7)=GradTmp(7)
412
                 Grad(IGeom,8)=GradTmp(8)
413
                 Idx=9
414
                 IBeg=4
415
              CASE DEFAULT
416
                 Idx=1
417
                 IBeg=1
418
              END SELECT
419
              DO I=IBeg,Nat
420
                 Grad(IGeom,Idx)=GradTmp(3*i-2)
421
                 Grad(IGeom,Idx+1)=GradTmp(3*i-1)
422
                 Grad(IGeom,Idx+2)=GradTmp(3*i)
423
                 Idx=Idx+3
424
              END DO
425
              DEALLOCATE(GradTmp)
426
           CASE ("CART","HYBRID")
427
              Grad(IGeom,:)=GradCart
428
           CASE DEFAULT
429
              WRITE(*,*) "Coord=",AdjustL(Trim(COORD))," not yet implemented in EgradPath.L257.STOP"
430
              STOP
431
           END SELECT
432

    
433
           IF (debug) THEN
434
              Line='DBG Path, GradTmp'
435
              Call PrintGeom(Line,Nat,NCoord,reshape(GRad(Igeom,1:NCoord),(/Ncoord/)),Coord,6,Atome,Order,OrderInv,IndZmat)
436
           END IF
437
        END DO ! matches  DO IGeom=IGeom0,IGeomF
438
        
439
     CASE ("GAUSSIAN")
440

    
441
        WRITE(IOOUT,*) " Creating the Input files and ListJob"
442
        ! We create the output files.
443
        IGeom0=2
444
        IGeomF=NGeomF-1
445
        PathCart=0.d0
446

    
447
        If (OptReac) IGeom0=1
448
        If (OptProd) IGeomF=NGeomF
449

    
450
        OPEN(IOTMP2,File="ListJob",STATUS="REPLACE")
451

    
452
        DO Igeom=IGeom0,IGeomF
453
           ! We first convert the geometry into a Cartesian one
454
           SELECT CASE(Coord)
455
           CASE ('ZMAT')
456
              GeomTmp=IntCoordF(IGeom,:)
457
              Call Int2cart(nat,indzmat,geomTmp,PathCart(1,IGeom))
458
           CASE ('BAKER')
459
              GeomTmp=IntCoordF(IGeom,:)
460
              !
461
              IF (IOpt .EQ. 0) THEN
462
                 ! EgradPath(...) is called only after the call of PathCreate(...)
463
                 ! and in PathCreate, IF (MOD(IOpt,IReparam).EQ.0) (which is always 
464
                 ! true if IOpt==0), THEN ExtraPol_baker(...) is called.
465
                 ! In ExtraPol_baker(...), XyzGeomF(...) is calculated upon converting
466
                 ! the interpolated internal coordinates into cartesian coordinates.
467
                 ! Thus here we don't need to reconvert the internal coordinates again
468
                 ! to the cartesian coordinates. 
469
                 DO I=1,Nat
470
                    PathCart(3*I-2,IGeom) = XyzGeomF(IGeom,1,I)
471
                    PathCart(3*I-1,IGeom) = XyzGeomF(IGeom,2,I)
472
                    PathCart(3*I,IGeom) = XyzGeomF(IGeom,3,I)
473
                 END DO
474
              ELSE
475

    
476
                 ! XyzGeomF(NGeomF,3,Nat).
477
                 x_k(:) = XyzGeomF(IGeom,1,:)
478
                 y_k(:) = XyzGeomF(IGeom,2,:)
479
                 z_k(:) = XyzGeomF(IGeom,3,:)
480

    
481
                 !Call ConvertBakerInternal_cart(GeomOld_all(IGeom,:),IntCoordI(IGeom,:), &
482
                 !                               x_k,y_k,z_k,x,y,z)
483
                 ! PathCart(3*Nat,NGeomF)
484
                 DO I=1,Nat
485
                    PathCart(3*I-2,IGeom) = x(I)
486
                    PathCart(3*I-1,IGeom) = y(I)
487
                    PathCart(3*I,IGeom) = z(I)
488
                 END DO
489

    
490
                 XyzGeomF(IGeom,1,:)=x(:)
491
                 XyzGeomF(IGeom,2,:)=y(:)
492
                 XyzGeomF(IGeom,3,:)=z(:)
493
              END IF
494
           CASE ('MIXED')
495
              GeomTmp=IntCoordF(IGeom,:)
496
              Call Mixed2cart(nat,indzmat,geomTmp,PathCart(1,IGeom))
497
           CASE ('CART','HYBRID')
498
!!! CAUTION : PFL 29.AUG.2008 ->
499
              ! XyzGeomI/F stored in (NGeomI/F,3,Nat) and NOT (NGeomI/F,Nat,3)
500
              ! This should be made  consistent !!!!!!!!!!!!!!!
501
              GeomTmp=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/))
502
!!! <- CAUTION : PFL 29.AUG.2008 
503
              PathCart(:,IGeom)=GeomTmp
504
           CASE DEFAULT
505
              WRITE(*,*) "Coord=",TRIM(Coord)," not recognized. EgradPath L75.STOP"
506
              STOP
507
           END SELECT
508

    
509
           WRITE(Line,'(I5)') IGeom
510
           FileInp="PathPar_" // TRIM(ADJUSTL(Line)) // ".com"
511
           WRITE(IOTMP2,'(1X,A)') TRIM(FileInp)
512

    
513
           OPEN(IOTMP,File=TRIM(FileInp))
514
           Current => Gauss_root
515
           DO WHILE (ASSOCIATED(Current%next))
516
              WRITE(IOTMP,'(1X,A)') Trim(current%line)
517
              WRITE(*,'(1X,A)') Trim(current%line)
518
              Current => current%next
519
           END DO
520

    
521
           WRITE(IOTMP,*) 
522

    
523
           Current => Gauss_comment
524
           DO WHILE (ASSOCIATED(Current%next))
525
              WRITE(IOTMP,'(1X,A)') Trim(current%line)
526
              Current => current%next
527
           END DO
528
           !  WRITE(IOOUT,"('Geometry ',I3,'/',I3,' for iteration ',I3)"),Igeom,NgeomF,Iopt
529

    
530
           WRITE(IOTMP,*) 
531
           WRITE(IOTMP,*) Trim(Gauss_charge)
532

    
533
           DO I=1,Nat
534
              If (renum) THEN
535
                 Iat=Order(I)
536
                 WRITE(IOTMP,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)) &
537
                      ,PathCart(Iat,IGeom),PathCart(Iat+Nat,IGeom),PathCart(Iat+2*Nat,IGeom)  &
538
                      ,TRIM(Gauss_Paste(I))
539
              ELSE
540
                 Iat=OrderInv(I)
541
                 WRITE(IOTMP,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)) &
542
                 ,PathCart(Iat,IGeom),PathCart(Iat+Nat,IGeom),PathCart(Iat+2*Nat,IGeom)  &
543
                      , TRIM(Gauss_Paste(Iat))
544
              END IF
545
           END DO
546

    
547
           WRITE(IOTMP,*) 
548

    
549
           Current => Gauss_End
550
           DO WHILE (ASSOCIATED(Current%next))
551
              WRITE(IOTMP,'(1X,A)') Trim(current%line)
552
              Current => current%next
553
           END DO
554

    
555
           WRITE(IOTMP,*) 
556
           CLOSE(IOTMP)
557

    
558
        END DO
559

    
560
        Close(IOTMP2)
561

    
562
! We launch the parallel calculations
563

    
564
        Line=Trim(ProgExe) 
565
        IF (DEBUG) WRITE(*,*)'RunCommand:',TRIM(Line)
566
        WRITE(IOOUT,*) " Launching Gaussian to compute the forces"
567
        call system(Line)
568
        IF (DEBUG) WRITE(*,*)'Back from RunCommand:'
569

    
570
! We read energies and gradients from the log files
571

    
572
        WRITE(*,*) "Gaussian over. Reading the Forces"
573

    
574
        DO IGeom=IGeom0,IGeomF
575
           WRITE(Line,'(I5)') IGeom
576
           FileInp="PathPar_" // TRIM(ADJUSTL(Line)) // ".log"
577
           OPEN(IOTMP,File=TRIM(FileInp))
578

    
579
  ! We first search for the forces
580
  READ(IOTMP,'(A)') LINE
581
  DO WHILE (INDEX(LINE,'Forces (Hartrees/Bohr)')==0)
582
     ! here, we have a problem, because there are so many ways to write E for Gaussian :-)
583
     ! but we do not really need E except if we want to weight the different points
584
     ! on the path... that will be done later :-)
585
     ! And I should use ConvGaussXmol ...
586
! PFL 3rd Jan 2008 ->
587
! I have finally upgraded the energy reading phase so that it should be able to read 
588
! many formats corresponding to HF, DFT, MP2, AM1, PM3, ONIOM with or w/o PCM
589
!
590
     
591
! For MP2, energy is after the last =
592
     IF ((Line(2:9)=="E2 =    ")) THEN
593
      Itmp1=Index(LINE,"=",BACK=.TRUE.)+1
594
    READ(LINE(Itmp1:),*) e
595
      END IF
596
! For other methods, it is after the first =
597
     IF ((LINE(2:9)=='Energy= ').OR.(Line(2:9)=="SCF Done").OR.(Line(2:9)=="ONIOM: e") &
598
   .OR.(Line(2:9)==" with al") &
599
         .OR.(Line(2:31)=="Counterpoise: corrected energy")) THEN
600
      Itmp1=Index(LINE,"=")+1
601
    READ(LINE(Itmp1:),*) e
602
  END IF
603
! <- PFL 3 Jan 2008
604
     READ(IOTMP,'(A)') LINE
605
  END DO
606
  READ(IOTMP,'(A)') LINE
607
  READ(IOTMP,'(A)') LINE
608
  DO I=1,Nat
609
     Iat=I
610
     IF (renum) Iat=Order(I)
611
     READ(IOTMP,*)  Itmp1,ITmp2, GradCart(3*Iat-2:3*Iat)
612
  END DO
613

    
614
! Gaussian gives the Forces in ua/a0, so we convert it into the 
615
! gradient in ua/Angstrom 
616
  gradCart=-1.0d0*Unit*gradCart
617
  CLOSE(IOTMP)
618
  Energies(IGeom)=E
619

    
620
  WRITE(*,*) "Forces and energy read for geometry ",IGeom
621
           ! We convert it into the right coordinate system
622
           ! This should be put into a subroutine (because it is also in egradient)
623
           SELECT CASE (COORD)
624
           CASE ("ZMAT")
625
              ALLOCATE(GradTmp(3*Nat))
626
              if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_int"
627
              CALL CalcBMat_int (nat, PathCart(1:3*Nat,Igeom), indzmat, dzdc, massat,atome)
628
              CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp)
629

    
630
              Grad(IGeom,1)=GradTmp(4)
631
              Grad(IGeom,2)=GradTmp(7)
632
              ! We might have troubles whith angles that are not in the [0:pi] range because,
633
              ! when converted to catesian coord, they do appear in the [0:Pi] range to gaussian...
634
              ! so that the derivative is not good, and a multiplicative factor should be added...
635
              !
636
              ! This in fact should be taken care of in B-mat calculation...
637
              !
638
              IF ((IntCoordF(Igeom,3).LE.0).OR.(IntCoordF(Igeom,3).GE.Pi)) THEN
639
                 Grad(IGeom,3)=-1.0d0*GradTmp(8)
640
              ELSE
641
                 Grad(IGeom,3)=GradTmp(8)
642
              END IF
643
              Idx=4
644
              DO I=4,Nat
645
                 Grad(IGeom,Idx)=GradTmp(3*i-2)
646
                 Grad(IGeom,Idx+1)=GradTmp(3*i-1)
647
                 Grad(IGeom,Idx+2)=GradTmp(3*i)
648
                 Idx=Idx+3
649
              END DO
650
              DEALLOCATE(GradTmp)
651
              ! We have the gradient in Cartesian coordinates... which is ok for COORD=Cart, Hybrid
652
              ! but we have to convert it into internal coordinates if COORD=Baker      
653
           CASE ('BAKER')
654
              ALLOCATE(GradTmp(3*Nat))
655
              GradTmp=0.d0
656
              ! Below is to be corrected.
657
              ! This is inside 'IF ((PROG=="VASP").AND.(RunMode=="PARA")) THEN'
658
              !DO I=1, 3*Nat
659
              ! here GradTmp and Grad are gradients in Baker coordinates
660
              ! Not implemented  IF ((PROG=="VASP").AND.(RunMode=="PARA"))
661
              ! GradTmp(:) = GradTmp(:) + BTransInv(:,I)*GradCart(I)
662
              !END DO
663
              Grad(IGeom,:) = GradTmp
664
              DEALLOCATE(GradTmp)
665
           CASE ('MIXED')
666
              ALLOCATE(GradTmp(3*Nat))
667
              if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_mixed"
668
              CALL CalcBMat_mixed(nat,PathCart(1:3*Nat,IGeom), indzmat, dzdc, massat,atome)
669
              CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp)
670
              DO I=1,Nat
671
                 WRITE(*,'(1X,3(1X,F10.5))') GradTmp(3*I-2:3*I)
672
              END DO
673
              SELECT CASE (NCART)
674
              CASE (1)
675
                 Grad(IGeom,1:3)=GradTmp(1:3)
676
                 Grad(IGeom,4)=GradTmp(4)
677
                 Grad(IGeom,5)=GradTmp(7)
678
                 Grad(IGeom,6)=GradTmp(8)
679
                 Idx=7
680
                 IBeg=4
681
              CASE(2)
682
                 Grad(IGeom,1:3)=GradTmp(1:3)
683
                 Grad(IGeom,4:6)=GradTmp(4:6)
684
                 Grad(IGeom,7)=GradTmp(7)
685
                 Grad(IGeom,8)=GradTmp(8)
686
                 Idx=9
687
                 IBeg=4
688
              CASE DEFAULT
689
                 Idx=1
690
                 IBeg=1
691
              END SELECT
692
              DO I=IBeg,Nat
693
                 Grad(IGeom,Idx)=GradTmp(3*i-2)
694
                 Grad(IGeom,Idx+1)=GradTmp(3*i-1)
695
                 Grad(IGeom,Idx+2)=GradTmp(3*i)
696
                 Idx=Idx+3
697
              END DO
698
              DEALLOCATE(GradTmp)
699
           CASE ("CART","HYBRID")
700
              Grad(IGeom,:)=GradCart
701
           CASE DEFAULT
702
              WRITE(*,*) "Coord=",AdjustL(Trim(COORD))," not yet implemented in EgradPath.L257.STOP"
703
              STOP
704
           END SELECT
705

    
706
           IF (debug) THEN
707
              Line='DBG Path, GradTmp'
708
              Call PrintGeom(Line,Nat,NCoord,reshape(GRad(Igeom,1:NCoord),(/Ncoord/)),Coord,6,Atome,Order,OrderInv,IndZmat)
709
           END IF
710

    
711
        END DO
712

    
713
     CASE DEFAULT
714
        WRITE(*,*) "Prog=",TRIM(Prog)," not yet supported for Para mode."
715
        STOP
716
     END SELECT
717

    
718
     DEALLOCATE(GradCart,PathCart)
719

    
720

    
721
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
722
!
723
! Serial executions
724
!
725
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
726
  ELSE ! matches IF (RunMode=="PARA") THEN
727
 ! We will launch all calculations sequentially
728
     ALLOCATE(GradTmp(NCoord))
729
     ! We have the new path, we calculate its energy and gradient
730
     IGeom0=2
731
     IGeomF=NGeomF-1
732
     IF (OptReac.OR.CalcEReac) IGeom0=1
733
     IF (OptProd.OR.CalcEProd) IGeomF=NGeomF
734
     CalcEReac=.FALSE.
735
     CalcEProd=.FALSE.
736
     ALLOCATE(GeomCart(Nat,3))
737

    
738
     DO IGeom=IGeom0,IGeomF
739
        WRITE(Line,"('Geometry ',I3,'/',I3,' for iteration ',I3)") Igeom,NgeomF,Iopt
740
        WRITE(IOOUT,*) "Creating Input for ", TRIM(Line)
741
!        if (debug) WRITE(*,*) Line
742
        SELECT CASE(Coord)
743
        CASE ('ZMAT','MIXED')
744
           GeomTmp=IntCoordF(IGeom,:)
745
        CASE ('BAKER')
746
           GeomTmp=IntCoordF(IGeom,:)
747
        CASE ('CART','HYBRID')
748
!!! CAUTION : PFL 29.AUG.2008 ->
749
           ! XyzGeomI/F stored in (NGeomI/F,3,Nat) and NOT (NGeomI/F,Nat,3)
750
           ! This should be made  consistent !!!!!!!!!!!!!!!
751
           GeomTmp=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/))
752
           !           GeomTmp=Reshape(XyzGeomF(IGeom,:,:),(/3*Nat/))
753
!!! <- CAUTION : PFL 29.AUG.2008
754
        CASE DEFAULT
755
           WRITE(*,*) "Coord=",TRIM(Coord)," not recognized in EgradPath. L299"
756
           STOP
757
        END SELECT
758

    
759
        IF (debug) THEN 
760
           WRITE(*,*) 'DBG Main, COORD=',TRIM(COORD),' IGeom=',IGeom,' Iopt=',Iopt
761
           WRITE(*,*) GeomTmp(1:min(NCoord,12))
762
        END IF
763

    
764
        GeomCart=0.d0
765
    
766
       ! GradTmp is gradient and calculated in Egrad.F, INTENT(OUT).
767
       ! GeomCart has INTENT(OUT)
768

    
769
       WRITE(IOOUT,*) "Computing and reading forces for ", TRIM(Line)
770
       Call EGrad(E,GeomTmp,GradTmp,NCoord,IGeom,IOpt,GeomCart) !GeomTmp=IntCoordF(IGeom,:)
771

    
772
    ! Egrad calls ConvertBakerInternal_cart to convert GeomTmp=IntCoordF(IGeom,:) into 
773
    ! GeomCart (Cartesian Coordinates) so that energy and gradients can be calculated 
774
    ! for each geometry.
775
        XyzGeomF(IGeom,1,:)=GeomCart(:,1)
776
        XyzGeomF(IGeom,2,:)=GeomCart(:,2)
777
        XyzGeomF(IGeom,3,:)=GeomCart(:,3)
778
      
779
        Energies(IGeom)=E
780

    
781
        if (debug) THEN
782
           Line='DBG Path, GradTmp'
783
           Call PrintGeom(Line,Nat,NCoord,GRadTmp,Coord,6,Atome,Order,OrderInv,IndZmat)
784
        END IF
785
        Grad(IGeom,:)=GradTmp
786
     END DO ! matches DO IGeom=IGeom0,IGeomF
787
     DEALLOCATE(GradTmp,GeomCart)
788

    
789
  END IF ! matches IF (RunMode=="PARA") THEN AFTER ELSE
790

    
791
  WRITE(IOOUT,*) " Forces all read. Moving on"
792

    
793

    
794
  DEALLOCATE(GeomTmp)
795
  DEALLOCATE(x,y,z)
796
  DEALLOCATE(x_k,y_k,z_k)
797
  if (debug) Call header('Exiting EgradPath')
798
  RETURN
799
999 WRITE(*,*) "EgradPath : We should not be here !"
800
   WRITE(*,*) "End of file happened too soon"
801
  STOP
802
9991 WRITE(*,*) "EgradPath : We should not be here !"
803
  WRITE(*,*) "EgradPath was Looking for 'EDIFF is reached'"
804
  STOP
805
9992 WRITE(*,*) "EgradPath : We should not be here !"
806
  WRITE(*,*) "EgradPath was Looking for 'TOTEN'"
807
  STOP
808
9993 WRITE(*,*) "EgradPath : We should not be here !"
809
  WRITE(*,*) "EgradPath was Looking for 'TOTAL-FORCE'"
810
  STOP
811
9994 WRITE(*,*) "EgradPath : We should not be here !"
812
  WRITE(*,*) "EgradPath was reading the forces "
813
  STOP
814

    
815
END SUBROUTINE EGRADPATH