Statistiques
| Révision :

root / src / Egrad.f90

Historique | Voir | Annoter | Télécharger (18,41 ko)

1
subroutine Egrad(E,Geom,Grad,NCoord,IGeom,IOpt,GeomCart,FOptGeom,GeomOld,GeomCart_old)
2

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

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

    
38
  use Path_module, only : Nat,AtName,Coord,dzdc,indzmat,Atome,massat, &
39
       prog,NCart,XyzGeomF, XyzGeomI, renum, &
40
       GeomOld_all,BTransInvF,BTransInv_local,UMatF,UMat_local &
41
       , BprimT,ScanCoord, Coordinate,NPrim,BMat_BakerT,BBT,BBT_inv &
42
      ,Order, OrderInv, XPrimitiveF,FPBC,XGeomRefPBC,YGeomRefPBC,ZGeomRefPBC
43

    
44
  ! IntCoordF(NGeomF,NCoord),GeomOld_all(NGeomF,NCoord)
45
  ! allocated in Path.f90
46

    
47
  use Io_module
48
  IMPLICIT NONE
49

    
50
  ! Energy (calculated if F300K=.F., else estimated)
51
  REAL(KREAL), INTENT (OUT) :: E
52
  ! NCoord: Number of the degrees of freedom
53
  ! IGeom: index of the geometry.
54
  INTEGER(KINT), INTENT (IN) :: NCoord, IGeom, IOpt
55
  ! Geometry at which gradient is calculated (cf Factual also):
56
  REAL(KREAL), INTENT (INOUT) :: Geom(NCoord)
57
  ! Gradient calculated at Geom geometry:
58
  REAL(KREAL), INTENT (OUT) :: Grad(NCoord)
59
  ! Cartesian geometry corresponding to (Internal Geometry) Geom:
60
  REAL(KREAL), INTENT (OUT) :: GeomCart(Nat,3)
61
!!! Optional, just for geometry optimization with Baker coordinates
62
  REAL(KREAL), INTENT (IN), OPTIONAL :: GeomCart_old(Nat,3)
63
  REAL(KREAL), INTENT (INOUT), OPTIONAL :: GeomOld(NCoord)
64
! FOptGeom is a flag indicating if we are doing a geom optimization
65
! it can be omitted so that we use a local flag: Flag_Opt_Geom
66
  LOGICAL,INTENT (IN), OPTIONAL :: FOptGeom
67
! if FOptGeom is given Flag_Opt_Geom=FOptGeom, else Flag_Opt_Geom=F
68
  LOGICAL  :: Flag_Opt_Geom
69

    
70
  ! ======================================================================
71

    
72
  LOGICAL :: debug
73
  REAL(KREAL), ALLOCATABLE :: GradTmp(:)
74
  REAL(KREAL), ALLOCATABLE :: GradCart(:)
75
  REAL(KREAL), ALLOCATABLE :: x(:), y(:), z(:)
76
  REAL(KREAL) ::  Pi
77
  REAL(KREAL) :: MRot(3,3), Rmsd
78

    
79
  INTEGER(KINT) :: iat, i, j, IBeg,Idx
80

    
81
  REAL(KREAL), ALLOCATABLE :: XPrimRef(:), XPrim(:) ! NPrim
82

    
83
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
84
!
85
!!!!!!!! PFL Debug
86
!
87
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
88
  REAL(KREAL), ALLOCATABLE :: GeomTmp(:,:) !3,Nat
89
  LOGICAL ::  FALOBBT,FALOBPrimt,FAloBBTInv
90
  LOGICAL :: DebugPFL
91

    
92
  ! ======================================================================
93
  INTERFACE
94
     function valid(string) result (isValid)
95
       CHARACTER(*), intent(in) :: string
96
       logical                  :: isValid
97
     END function VALID
98
  END INTERFACE
99
  ! ======================================================================
100

    
101
  Pi=dacos(-1.0d0)
102

    
103
  if (present(FOptGeom)) THEN
104
     Flag_Opt_Geom=FOptGeom
105
  ELSE
106
     Flag_Opt_Geom=.FALSE.
107
  END IF
108

    
109
  debug=valid('EGRAD')
110
  debugPFL=valid('bakerPFL')
111
  if (debug) Call Header("Entering Egrad")
112

    
113
  if (debug) Print *, 'EGrad.f90, L73, IOpt=', IOpt, ' Flag_Opt_Geom=',Flag_Opt_Geom
114

    
115
  Grad=0.
116
  E=0.
117

    
118

    
119
  ALLOCATE(GradCart(3*Nat))
120
  ALLOCATE(x(Nat),y(Nat),z(Nat))
121
  ALLOCATE(XPrimRef(NPrim),XPrim(NPrim))
122

    
123
  SELECT CASE (COORD)
124
  CASE ('ZMAT')
125
     ! In order to avoid problem with numbering and linear angles/diehedral, we convert the
126
     ! zmat into cartesian coordinates
127
     Call Int2Cart(nat,indzmat,Geom,GeomCart)
128
! In case of PBC calculations, we have to re-orient the geometry onto the user initial geometry
129
     If (FPBC) THEN
130
! we align this geometry on the initial one
131
        if (debug) THEN
132
           WRITe(*,*) "We are orientating..."
133
           WRITE(*,*) "Geom before orientation"
134
           WRITE(*,*) Nat
135
           WRITE(*,*) ""
136
           DO I=1,Nat
137
              If (renum) Iat=Order(I)
138
              WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomCart(I,1),GeomCart(I,2),GeomCart(I,3)
139
           END DO
140
        END IF
141

    
142
        IF (Renum) THEN
143
           DO I=1,Nat
144
              Iat=Order(I)
145
              X(I)=GeomCart(Iat,1)
146
              Y(I)=GeomCart(Iat,2)
147
              Z(I)=GeomCart(Iat,3)
148
           END DO
149
        ELSE
150
           X(1:Nat)=GeomCart(1:Nat,1)
151
           Y(1:Nat)=GeomCart(1:Nat,2)
152
           Z(1:Nat)=GeomCart(1:Nat,3)
153
        END IF
154

    
155
        if (debug) then
156
           WRITE(*,*) "Geom before orientation after reorderring"
157
           WRITE(*,*) Nat
158
           WRITE(*,*) ""
159
           DO I=1,Nat
160
!              Iat=I
161
!              If (Renum) Iat=Order(I)
162
              WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)),X(I),Y(I),Z(I)
163
           END DO
164
           WRITE(*,*) "Ref Geom"
165
           WRITE(*,*) Nat
166
           WRITE(*,*) ""
167
           DO I=1,Nat
168
              WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)),XGeomRefPBC(I),YGeomRefPBC(I),ZGeomRefPBC(I)
169
           END DO
170
        END IF
171

    
172
        Call CalcRmsd(Nat,XGeomRefPBC,YGeomRefPBC,ZGeomRefPBC, &
173
             X,Y,Z, MRot, Rmsd,.TRUE.,.TRUE.) 
174

    
175
        If (DEBUG) THEN
176
           WRITE(*,*) "Geom AFTER orientation"
177
           WRITE(*,*) Nat
178
           WRITE(*,*) ""
179
           DO I=1,Nat
180
              WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)),X(I),Y(I),Z(I)
181
           END DO
182
        END IF
183
        
184
        If (Renum)  THEN
185
           Do I=1,Nat
186
              Iat=orderInv(I)
187
              GeomCart(Iat,1)=X(I)
188
              GeomCart(Iat,2)=Y(I)
189
              GeomCart(Iat,3)=Z(I)
190
           END DO
191
        END IF
192
     END IF
193

    
194
  CASE ('BAKER')
195
     XPrimRef=XPrimitiveF(IGeom,:)
196
     IF (Flag_Opt_Geom) THEN
197
        IF (IOpt .EQ. 1) THEN
198
           GeomCart(:,1) = XyzGeomI(IGeom,1,:)
199
           GeomCart(:,2) = XyzGeomI(IGeom,2,:)
200
           GeomCart(:,3) = XyzGeomI(IGeom,3,:)
201
        ELSE
202
           if (debug) WRITE(*,*) 'Before Call ConvertBakerInternal_cart; L125, Egrad.f90'
203
           if (.NOT.present(GeomOld)) THEN
204
              WRITE(*,*) "ERROR: GeomOld not passed as an argument"
205
              STOP
206
           END IF
207
           WRITE(*,*) 'GeomOld='
208
           WRITE(*,'(12(1X,F6.3))') GeomOld
209
           WRITE(*,*) 'Geom='
210
           WRITE(*,'(12(1X,F6.3))') Geom
211
           if (.NOT.present(GeomCart_Old)) THEN
212
              WRITE(*,*) "ERROR: GeomCart_Old not passed as an argument"
213
              STOP
214
           END IF
215

    
216
           WRITE(*,*) 'GeomCart_old='
217
           WRITE(*,'(20(1X,F6.3))') GeomCart_old(1:Nat,1:3)
218
           Call ConvertBakerInternal_cart(GeomOld,Geom,GeomCart_old(:,1), &
219
                GeomCart_old(:,2),GeomCart_old(:,3),x,y,z,XPrim,XPrimRef)
220
           GeomCart(:,1) = x(:)
221
           GeomCart(:,2) = y(:)
222
           GeomCart(:,3) = z(:)
223
        END IF
224
     ELSE
225
        IF (IOpt .EQ. 0) THEN  
226
           GeomCart(:,1) = XyzGeomF(IGeom,1,:)
227
           GeomCart(:,2) = XyzGeomF(IGeom,2,:)
228
           GeomCart(:,3) = XyzGeomF(IGeom,3,:)
229
        ELSE
230
           ! IntCoordF(NGeomF,NCoord), XyzGeomF(NGeomF,3,Nat)
231
           ! Geom has to be converted into x,y,z
232
           ! GeomOld_all and XyzGeomF are old geometry in internal and cartesian coords resp.
233
           DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart()
234
              BTransInv_local(I,:) = BTransInvF(IGeom,I,:)
235
              UMat_local(:,I) = UMatF(IGeom,:,I)
236
           END DO
237
           if (debug) Print *, 'I am before Call ConvertBakerInternal_cart; L160, Egrad.f90'
238
           WRITE(*,*) 'GeomOld='
239
           WRITE(*,'(12(1X,F6.3))') GeomOld_all(IGeom,:)
240
           WRITE(*,*) 'Geom='
241
           WRITE(*,'(12(1X,F6.3))') Geom
242
           WRITE(*,*) 'DBG Egrad L165 GeomCart_old='
243
           DO I=1,Nat
244
              WRITE(*,'(3(1X,F12.8))') XyzGeomF(IGeom,:,I)
245
           END DO
246

    
247
           Call ConvertBakerInternal_cart(GeomOld_all(IGeom,:),Geom,XyzGeomF(IGeom,1,:), &
248
          XyzGeomF(IGeom,2,:),XyzGeomF(IGeom,3,:),x,y,z,XPrim,XPrimRef)
249
           if (debug) Print *, 'I am after Call ConvertBakerInternal_cart; L111, Egrad.f90'
250
           DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart()
251
              BTransInvF(IGeom,I,:) = BTransInv_local(I,:)
252
           END DO
253
           ! GeomCart is actually XyzCoord and has INTENT(OUT) in this subroutine.
254
           GeomCart(:,1) = x(:)
255
           GeomCart(:,2) = y(:)
256
           GeomCart(:,3) = z(:)
257
        END IF ! matches IF (IOpt .EQ. 0) THEN
258
     END IF
259
  CASE ('MIXED')
260
!  write(*,*) "Coucou 4-mixed"
261
     Call Mixed2Cart(Nat,indzmat,geom,GeomCart)
262
  CASE ('CART')
263

    
264
     GeomCart=reshape(Geom,(/Nat,3/))
265
     if (debug) THEN
266
        WRITE(*,*) "Coord=CART... in egrad"
267
        DO Iat=1,Nat
268
           WRITE(IOTMP,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),Geom(3*Iat-2:3*Iat)
269
        END DO
270
     END IF
271
  CASE ('HYBRID')
272
!  write(*,*) "Coucou 4-hybrid"
273
        GeomCart=reshape(Geom,(/Nat,3/))
274
  CASE DEFAULT
275
     WRITE (*,*) "Coord=",TRIM(COORD)," not recognized. Stop"
276
     STOP
277
  END SELECT
278
  !WRITE(*,*) Nat
279
  !WRITE(*,*) 'GeomCart in Egrad_baker'
280
  !DO I=1,Nat
281
  !  WRITE(*,'(1X,A,3(1X,F12.8))') AtName(I),GeomCart(I,1:3)
282
  !END DO
283

    
284

    
285

    
286
  SELECT CASE (Prog)
287
  CASE ('GAUSSIAN')
288
! we call the Gaussian routine.
289
! it will return the energy and the gradient in cartesian coordinates.
290
! Gradient calculated at GeomCart geometry and stored in GradCart, which has INTENT(OUT)
291
     Call egrad_gaussian(E,GeomCart,GradCart)
292
  CASE ('MOPAC')
293
! we call the Mopac routine.
294
! it will return the energy and the gradient in cartesian coordinates.
295
! Gradient calculated at GeomCart geometry and stored in GradCart, which has INTENT(OUT)
296
     Call egrad_mopac(E,GeomCart,GradCart)
297
  CASE ('VASP')
298
     Call egrad_vasp(E,Geomcart,GradCart)
299
  CASE ('SIESTA')
300
     Call egrad_siesta(E,Geomcart,GradCart)
301
  CASE ('TURBOMOLE')
302
     Call egrad_turbomole(E,Geomcart,GradCart)
303
  CASE ('EXT')
304
     Call egrad_ext(E,Geomcart,GradCart)
305
  CASE ('TEST')
306
     Call egrad_test(Nat,E,Geomcart,GradCart)
307
  CASE ('TEST2D')
308
     Call egrad_test_2D(Nat,E,Geomcart,GradCart)
309
! Chamfre is not public. Contact Wei.Dong@ens-lyon.fr 
310
! and optnpath@gmail.com if you want it.
311
!  CASE ('CHAMFRE')
312
!     Call egrad_chamfre(Nat,E,Geomcart,GradCart)
313
  CASE ('LEPS')
314
     Call egrad_LEPS(Nat,E,Geomcart,GradCart)
315
  END SELECT
316
  if (debug) THEN
317
     WRITE(*,*) 'DBG EGRAD, GradCart read'
318
     DO I=1,Nat
319
        Iat=I
320
        if (renum) Iat=orderInv(I)
321
        WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GradCart(3*I-2:3*I)
322
     END DO
323
  END IF
324

    
325
!  If (PROG=="VASP") STOP
326

    
327

    
328
  ! We have the gradient in Cartesian coordinates... which is ok for COORD=Cart, Hybrid
329
  !  but we have to convert it into Zmat if COORD=Zmat
330
  SELECT CASE (COORD)
331
     CASE ("ZMAT")
332
        ALLOCATE(GradTmp(3*Nat))
333
        if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_int"
334
        CALL CalcBMat_int (nat, reshape(GeomCart,(/3,Nat/),ORDER=(/2,1/)), indzmat, dzdc, massat,atome)
335

    
336
        if (debug) WRITE(*,*) "DBG EGRAD Calling ConvGrad_Cart2Int"
337
        CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp)
338

    
339
        if (debug) WRITE(*,*) "DBG EGRAD Storing Grad"
340
     Grad(1)=GradTmp(4)
341
     Grad(2)=GradTmp(7)
342
! We might have troubles whith angles that are not in the [0:pi] range because,
343
! when converted to catesian coord, they do appear in the [0:Pi] range to gaussian...
344
! so that the derivative is not good, and a multiplicative factor should be added...
345
!
346
! This in fact should be taken care of in B mat calculation... 
347
!
348
     IF ((Geom(3).LE.0).OR.(Geom(3).GE.Pi)) THEN
349
        Grad(3)=-1.0d0*GradTmp(8)
350
     ELSE
351
        Grad(3)=GradTmp(8)
352
     END IF
353
     Idx=4
354
     DO I=4,Nat
355
        Grad(Idx)=GradTmp(3*i-2)
356
        Grad(Idx+1)=GradTmp(3*i-1)
357
        Grad(Idx+2)=GradTmp(3*i)
358
        Idx=Idx+3
359
     END DO
360
     DEALLOCATE(GradTmp)
361
   CASE ('BAKER')
362
     ! We have the gradient in Cartesian coordinates... which is ok for COORD=Cart, Hybrid
363
     ! but we have to convert it into internal coordinates if COORD=Baker	 
364
!!!!!!!!!!!!!!!!!!!!
365
     !
366
     !   PFL Debug
367
     !
368
!!!!!!!!!!!!!!!!!!!!
369
     if (debugPFL) THEN
370
        WRITE(*,*) "DBG PFL Egrad_Baker... computing dzdc"
371
     if (.not.ALLOCATED(indzmat)) THEN
372
        ALLOCATE(indzmat(Nat,5))
373
     IndZmat=0
374
     Indzmat(1,1)=1
375
     IndZmat(2,1)=2
376
     IndZmat(2,2)=1
377
     IndZmat(3,1)=3
378
     IndZmat(3,2)=2
379
     IndZmat(3,3)=1
380
     IndZmat(4,1)=4
381
     IndZmat(4,2)=3
382
     IndZmat(4,3)=2
383
     IndZmat(4,4)=1
384
     END IF
385
     IF (.NOT.ALLOCATED(DzDc)) THEN
386
        ALLOCATE(DzDc(3,nat,3,Nat))
387
     END IF
388
     if (.NOT.Allocated(GeomTmp)) Allocate(GeomTmp(3,Nat))                                            
389
     DO I=1,Nat
390
     GeomTmp(1,I)=GeomCart(OrderInv(I),1)
391
     GeomTmp(2,I)=GeomCart(OrderInv(i),2)
392
     GeomTmp(3,I)=GeomCart(OrderInv(i),3)
393
     END DO
394

    
395
     DzDc=0.d0
396
     CALL CalcBMat_int (nat, GeomTmp, indzmat, dzdc, massat,atome)     
397

    
398
     END IF ! if (debugPFL)
399
!!!!!!!!!!!!!!!!!!!!!!!!!
400
     ! Debugging PFL
401
!!!!!!!!!!!!!!!!!!!!!!!!
402

    
403
     WRITE(*,*) "BTransInv_local Trans that is used originally"
404
     DO J=1,3*Nat
405
        WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
406
     END DO
407

    
408
     WRITE(*,*) "Calculating actual values using GeomCart"
409
     if (.NOT.Allocated(GeomTmp)) Allocate(GeomTmp(3,Nat))
410
     GeomTmp(1,:)=GeomCart(1:Nat,1)
411
     GeomTmp(2,:)=GeomCart(1:Nat,2)
412
     GeomTmp(3,:)=GeomCart(1:Nat,3)
413

    
414
     ! Computing B^prim:
415
     FAloBBT=.NOT.ALLOCATED(BBT)
416
     FAloBBTInv=.NOT.ALLOCATED(BBT_inv)
417
     FAloBPrimT=.NOT.ALLOCATED(BprimT)
418
     if (FAloBPrimT) ALLOCATE(Bprimt(3*Nat,NPrim))
419
     if (FAloBBT) ALLOCATE(BBt(NCoord,NCoord))
420
     if (FAloBBTInv) ALLOCATE(BBt_inv(NCoord,NCoord))
421
     BprimT=0.d0
422
     ScanCoord=>Coordinate
423
     I=0
424
     DO WHILE (Associated(ScanCoord%next))
425
        I=I+1
426
        SELECT CASE (ScanCoord%Type)
427
        CASE ('BOND') 
428
           CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2,GeomTmp,BprimT(1,I))
429
        CASE ('ANGLE')
430
           CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,GeomTmp,BprimT(1,I))
431
        CASE ('DIHEDRAL')
432
           CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,ScanCoord%At4,GeomTmp,BprimT(1,I))
433
        END SELECT
434
        ScanCoord => ScanCoord%next
435
     END DO
436

    
437
     if (debug) THEN
438
        WRITE(*,*) "Bprim "
439
        DO J=1,3*Nat
440
           WRITE(*,'(50(1X,F12.6))') BprimT(J,:)
441
        END DO
442
     END IF
443

    
444
     BMat_BakerT = 0.d0
445
     DO I=1,NCoord
446
        DO J=1,NPrim
447
           !BprimT is transpose of B^prim.
448
           !B = UMat^T B^prim, B^T = (B^prim)^T UMat
449
           BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat_local(J,I)
450
        END DO
451
     END DO
452

    
453
     BBT = 0.d0
454
     DO I=1,NCoord
455
        DO J=1,3*Nat   ! BBT(:,I) forms BB^T
456
           BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I)
457
        END DO
458
     END DO
459

    
460
     BBT_inv = 0.d0
461

    
462
     Call GenInv(NCoord,BBT,BBT_inv,NCoord)
463

    
464
     !Print *, 'BBT_inv='
465
     DO J=1,NCoord
466
        ! WRITE(*,'(50(1X,F10.2))') BBT_inv(:,J)
467
        ! Print *, BBT_inv(:,J)
468
     END DO
469
     !Print *, 'End of BBT_inv'
470

    
471
     ! Calculation of (B^T)^-1 = (BB^T)^-1B:
472
     BTransInv_local = 0.d0
473
     DO I=1,3*Nat
474
        DO J=1,NCoord
475
           BTransInv_local(:,I)=BTransInv_local(:,I)+BBT_inv(:,J)*BMat_BakerT(I,J)
476
        END DO
477
     END DO
478

    
479
     Print *, 'BMat_BakerT='
480
     DO J=1,3*Nat
481
        WRITE(*,'(50(1X,F12.8))') BMat_BakerT(:,J)
482
     END DO
483

    
484
     WRITE(*,*) "BTransInv_local Trans corresponding to GeomCart"
485
     DO J=1,3*Nat
486
        WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
487
     END DO
488

    
489
     if (FAloBPrimT) DEALLOCATE(Bprimt)
490
     if (FAloBBT) DEALLOCATE(BBt)
491
     if (FAloBBTInv) DEALLOCATE(BBt_inv)
492

    
493
     Grad=0.d0
494
     DO I=1, 3*Nat
495
        ! Here Grad is gradient in Baker coordinates. GradCart(3*Nat)
496
        Grad(:) = Grad(:) + BTransInv_local(:,I)*GradCart(I) !BTransInv_local = BTransInv in Opt_Geom.f90
497
     END DO
498
     !WRITE(*,*) 'In Egrad.f90, L263, Gradient:' 
499
     !WRITE(*,'(12(1X,F8.4))') Grad(1:NCoord)
500

    
501

    
502
     CASE ('MIXED')
503
        ALLOCATE(GradTmp(3*Nat))
504
        if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_mixed"
505
        CALL CalcBMat_mixed (nat, reshape(GeomCart,(/3,Nat/),ORDER=(/2,1/)), indzmat, dzdc, massat,atome)
506

    
507
        if (Debug) THEN
508
           WRITE(*,*) "DzDc"
509
           DO I=1,Nat
510
              DO J=1,3
511
                 WRITE(*,'(50(1X,F12.6))') dzdc(J,I,:,:)
512
              END DO
513
           END DO
514
        END IF
515
       
516

    
517
        CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp)
518
        DO I=1,Nat
519
           WRITE(*,'(1X,3(1X,F10.5))') GradTmp(3*I-2:3*I)
520
        END DO
521
        SELECT CASE (NCART)
522
           CASE (1)
523
              Grad(1:3)=GradTmp(1:3)
524
              Grad(4)=GradTmp(4)
525
              Grad(5)=GradTmp(7)
526
              Grad(6)=GradTmp(8)
527
              Idx=7
528
              IBeg=4
529
           CASE(2)
530
              Grad(1:3)=GradTmp(1:3)
531
              Grad(4:6)=GradTmp(4:6)
532
              Grad(7)=GradTmp(7)
533
              Grad(8)=GradTmp(8)
534
              Idx=9
535
               IBeg=4
536
            CASE DEFAULT
537
               Idx=1
538
               IBeg=1
539
            END SELECT
540
     DO I=IBeg,Nat
541
        Grad(Idx)=GradTmp(3*i-2)
542
        Grad(Idx+1)=GradTmp(3*i-1)
543
        Grad(Idx+2)=GradTmp(3*i)
544
        Idx=Idx+3
545
     END DO
546
     DEALLOCATE(GradTmp)
547
  CASE ("CART","HYBRID")
548
     Grad=GradCart
549
  CASE DEFAULT
550
     WRITE(*,*) "Coord=",AdjustL(Trim(COORD))," not yet implemented in Egradients. STOP"
551
     STOP
552
  END SELECT
553

    
554
  DEALLOCATE(GradCart)
555
  DEALLOCATE(x,y,z)
556

    
557
  IF (Debug) WRITE(*,*) 'DBG EGRAD grad',grad(1:NCoord)
558
  if (debug) Call Header("Egrad Over")
559

    
560
  !999 CONTINUE
561
  !if (.NOT.Ftmp) WRITE(*,*) 'We should not be here !!!!'
562
  !STOP
563
  ! ======================================================================
564
end subroutine Egrad
565