Statistiques
| Révision :

root / src / egrad_gaussian.f90 @ 2

Historique | Voir | Annoter | Télécharger (6,63 ko)

1
subroutine egrad_gaussian(e,geomcart,gradcart)
2

    
3
  ! This routines calculates the energy and the gradient of 
4
  ! a molecule, using Gaussian 
5

    
6
  use Path_module, only : Nat, renum,Order,OrderInv,AtName, Coord, dzdc, indzmat,Nom,Atome, massat, unit,ProgExe
7
  use Io_module
8

    
9
  IMPLICIT NONE
10

    
11
  ! Energy (calculated if F300K=.F., else estimated)
12
  REAL(KREAL), INTENT (OUT) :: e
13
  ! Nb degree of freedom
14
  REAL(KREAL), INTENT (IN) :: geomcart(Nat,3)
15
  ! Gradient calculated at Geom geometry
16
  REAL(KREAL), INTENT (OUT) :: gradcart(3*NAt)
17

    
18
  ! ======================================================================
19

    
20
  character(LCHARS) :: LINE
21

    
22
  logical           :: debug, G03Ok
23
  LOGICAL :: fexist, FSim
24
  LOGICAL, SAVE :: first=.true.
25
  LOGICAL, ALLOCATABLE :: Done(:)
26

    
27
  REAL(KREAL), SAVE :: Eold=1.e6
28
  REAL(KREAL), ALLOCATABLE :: GradTmp(:)
29

    
30
  REAL(KREAL) :: d, a_val, Pi
31

    
32
  REAL(KREAL) :: coef,x
33
  INTEGER(KINT) :: ItG03
34
  INTEGER(KINT) :: iat, jat, kat, i, j, n3at, absidg, absidg2
35
  INTEGER(KINT) :: kTmp, Istart,ITmp1,ITmp2, Idx
36
  INTEGER(KINT), PARAMETER :: IOLOG=12, IOCOM=11
37

    
38
  CHARACTER(132) :: FileIn, FileOut, FileChk
39

    
40
  CHARACTER(3) :: SepIn=' < ', SepOut=' > '
41
  CHARACTER(LCHARS) :: ListName, TitleTmp, CH32SVAR1
42
  CHARACTER(VLCHARS), SAVE :: RstrtCopy, RunCommand
43
  LOGICAL, SAVE :: FCopyRstrt=.False., FOrderChecked=.False.
44
  LOGICAL   :: FRdyn,FStopNucl, FTmp, Tchk,Tchk1
45
  INTEGER(kint) :: NbLists,LastIt,Nat4,NStep, Firstit
46
  INTEGER(KINT) :: NStepAd,NStepTmp
47
  INTEGER(KINT) :: IShowTmp
48
  REAL(KREAL)   :: FricPsiMin,FricPsiT, FricNuclTmp
49

    
50
  INTEGER(KINT), PARAMETER :: NbExtName=4
51

    
52
  INTEGER(KINT) :: ICouc
53

    
54
  INTEGER(KINT) :: ILine
55
  INTEGER(KINT) :: NPulses, PulseLen, NStepWarm,NStepAv,NStepEq,NStepTot
56
  REAL(KREAL) :: TempWarm,Mean,Slope,Dev,RTmp1,RTmp2
57

    
58
  ! ======================================================================
59

    
60
  LOGICAL, EXTERNAL :: valid
61

    
62
  ! ======================================================================
63

    
64
  Pi=dacos(-1.0d0)
65
  n3at=3*nat
66

    
67
  debug=valid('EGRAD')
68
  if (debug) Call Header("Entering Egrad_gaussian")
69

    
70
  if (first) THEN
71
     First=.FALSE.
72
     call system("uname > Path.tmp")
73
     OPEN(IOTMP,FILE='Path.tmp')
74
     READ(IOTMP,'(A)') Line
75
     CLOSE(IOTMP)
76
     IF (index(Line,'CYGWIN').NE.0) THEN
77
        SepIn='   '
78
        SepOut='   '
79
     END IF
80
  END IF
81

    
82
  gradcart=0.
83
  E=0.
84
  FileIn=Trim(CalcName) // "." // Trim(ISuffix)
85
  FileOut=Trim(CalcName) // "." // Trim(OSuffix)
86
  FileChk=Trim(CalcName) // ".chk"
87
  RunCommand=Trim(ProgExe) // SepIn // Trim(FileIn) // SepOut // Trim(FileOut)
88

    
89
  IF (DEBUG) WRITE(*,*)'RunCommand:',TRIM(RunCommand)
90

    
91
  ! we create the input file
92

    
93
  OPEN(IOTMP,File=FileIn)
94

    
95
  Current => Gauss_root
96
  DO WHILE (ASSOCIATED(Current%next))
97
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
98
     WRITE(*,'(1X,A)') Trim(current%line)
99
     Current => current%next
100
  END DO
101

    
102
  WRITE(IOTMP,*) 
103

    
104
  Current => Gauss_comment
105
  DO WHILE (ASSOCIATED(Current%next))
106
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
107
     Current => current%next
108
  END DO
109
  !  WRITE(IOOUT,"('Geometry ',I3,'/',I3,' for iteration ',I3)"),Igeom,NgeomF,Iopt
110

    
111
  WRITE(IOTMP,*) 
112
  WRITE(IOTMP,*) Trim(Gauss_charge)
113

    
114
  DO I=1,Nat
115
     If (renum) THEN
116
        Iat=Order(I)
117
        WRITE(IOTMP,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)),GeomCart(Iat,:), TRIM(Gauss_Paste(I))
118
     ELSE
119
        Iat=OrderInv(I)
120
        WRITE(IOTMP,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomCart(I,:), TRIM(Gauss_Paste(Iat))
121
     END IF
122
  END DO
123

    
124
  WRITE(IOTMP,*) 
125

    
126
  Current => Gauss_End
127
  DO WHILE (ASSOCIATED(Current%next))
128
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
129
     Current => current%next
130
  END DO
131

    
132
  WRITE(IOTMP,*) 
133
  CLOSE(IOTMP)
134

    
135
  IF (debug) THEN
136
     WRITE(*,*) 'DBG EGRAD ' //  Trim(FileIn),' COORD=',TRIM(COORD)
137
     call system('cat ' // Trim(FileIn))
138
  END IF
139

    
140
!!! PFL 15th March 2008 ->
141
! Sometimes for unknown reasons G03 fails.
142
! We thus add one test to check that Gaussian has finisehd properly.
143
! We also check that we do not run an infinite loop...
144

    
145
 G03Ok=.FALSE.
146
 ItG03=0
147

    
148
  DO WHILE ((.NOT.G03Ok).AND.(ItG03<3))
149
   ItG03=ItG03+1
150
  call system(RunCommand)
151
 OPEN(IOTMP,FILE=FileOut, STATUS='old', POSITION='APPEND')
152
 BACKSPACE(IOTMP)
153
 READ(IOTMP,'(A)') Line
154
 IF (LINE(2:19).EQ.'Normal termination')  G03Ok=.TRUE.
155
  END DO
156
  CLOSE(IOTMP)
157
  IF (.NOT.G03Ok) THEN
158
     WRITE(*,*) "Egrad_gaussian Failed..."
159
     WRITE(*,*) "Wrong termination of Gaussian after 3 tries. Check Input and geometry"
160
     STOP
161
  END IF
162

    
163
  if (debug) WRITE(*,*) 'DBG EGRAD, back from calculation'
164

    
165
  ! Whatever the coordinate system, we read the cartesian gradient
166
  ! and we convert it to Zmat or other if needed
167

    
168
  OPEN(IOTMP,FILE=FileOut, STATUS='old')
169
  ! We first search for the forces
170
  READ(IOTMP,'(A)') LINE
171
  DO WHILE (INDEX(LINE,'Forces (Hartrees/Bohr)')==0)
172
     ! here, we have a problem, because there are so many ways to write E for Gaussian :-)
173
     ! but we do not really need E except if we want to weight the different points
174
     ! on the path... that will be done later :-)
175
     ! And I should use ConvGaussXmol ...
176
! PFL 3rd Jan 2008 ->
177
! I have finally upgraded the energy reading phase so that it should be able to read 
178
! many formats corresponding to HF, DFT, MP2, AM1, PM3, ONIOM with or w/o PCM
179
     
180
! For MP2, energy is after the last =
181
     IF ((Line(2:9)=="E2 =    ")) THEN
182
	    Itmp1=Index(LINE,"=",BACK=.TRUE.)+1
183
		READ(LINE(Itmp1:),*) e
184
      END IF
185
! For other methods, it is after the first =
186
     IF ((LINE(2:9)=='Energy= ').OR.(Line(2:9)=="SCF Done").OR.(Line(2:9)=="ONIOM: e") &
187
	 .OR.(Line(2:9)==" with al") &
188
         .OR.(Line(2:31)=="Counterpoise: corrected energy")) THEN
189
	    Itmp1=Index(LINE,"=")+1
190
		READ(LINE(Itmp1:),*) e
191
	END IF
192
! <- PFL 3 Jan 2008
193
     READ(IOTMP,'(A)') LINE
194
  END DO
195
  if (debug) WRITE(*,*) "GradCart reading - renum=",Renum
196
  READ(IOTMP,'(A)') LINE
197
  READ(IOTMP,'(A)') LINE
198
  DO I=1,Nat
199
     Iat=I
200
     IF (renum) Iat=Order(I)
201
     READ(IOTMP,*)  Itmp1,ITmp2, GradCart(3*Iat-2:3*Iat)
202
     if (debug) WRITE(*,*) "I,Iat,GradCart:",I,Iat,GradCart(3*Iat-2:3*Iat)
203
  END DO
204

    
205
! Gaussian gives the Forces in ua/a0, so we convert it into the 
206
! gradient in ua/Angstrom 
207
  gradCart=-1.0d0*gradCart*Unit
208

    
209
!  if (debug.AND.(COORD.EQ.'ZMAT')) THEN
210
!     DO WHILE (INDEX(LINE,'Internal Coordinate Forces')==0)
211
!        READ(IOTMP,'(A)') LINE
212
!!        WRITE(*,*) 'Pas bon:' // TRIM(LINE)
213
!     END DO
214
!     WRITE(*,*) TRIM(LINE)
215
!     DO I=1,Nat+2
216
!        READ(IOTMP,'(A)') LINE
217
!        WRITE(*,*) TRIM(LINE)
218
!     END DO
219
!  END IF
220

    
221
  CLOSE(IOTMP)
222

    
223
  if (debug) Call header("Egrad_gaussian Over")
224

    
225
  RETURN
226

    
227
999 CONTINUE
228
  if (.NOT.Ftmp) WRITE(*,*) 'We should not be here !!!!'
229
  STOP
230
  ! ======================================================================
231
end subroutine egrad_gaussian