Statistiques
| Révision :

root / src / egrad_gaussian.f90 @ 12

Historique | Voir | Annoter | Télécharger (7,16 ko)

1 1 pfleura2
subroutine egrad_gaussian(e,geomcart,gradcart)
2 1 pfleura2
3 1 pfleura2
  ! This routines calculates the energy and the gradient of
4 1 pfleura2
  ! a molecule, using Gaussian
5 1 pfleura2
6 12 pfleura2
!----------------------------------------------------------------------
7 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
8 12 pfleura2
!  Centre National de la Recherche Scientifique,
9 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
10 12 pfleura2
!
11 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
12 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
13 12 pfleura2
!
14 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
15 12 pfleura2
!  Contact: optnpath@gmail.com
16 12 pfleura2
!
17 12 pfleura2
! This file is part of "Opt'n Path".
18 12 pfleura2
!
19 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
20 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
21 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
22 12 pfleura2
!  or (at your option) any later version.
23 12 pfleura2
!
24 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
25 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
26 12 pfleura2
!
27 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
28 12 pfleura2
!  GNU Affero General Public License for more details.
29 12 pfleura2
!
30 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
31 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
32 12 pfleura2
!
33 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
34 12 pfleura2
! for commercial licensing opportunities.
35 12 pfleura2
!----------------------------------------------------------------------
36 12 pfleura2
37 8 pfleura2
  use Path_module, only : Nat, renum,Order,OrderInv,AtName, Coord,unit,ProgExe
38 1 pfleura2
  use Io_module
39 1 pfleura2
40 1 pfleura2
  IMPLICIT NONE
41 1 pfleura2
42 1 pfleura2
  ! Energy (calculated if F300K=.F., else estimated)
43 1 pfleura2
  REAL(KREAL), INTENT (OUT) :: e
44 1 pfleura2
  ! Nb degree of freedom
45 1 pfleura2
  REAL(KREAL), INTENT (IN) :: geomcart(Nat,3)
46 1 pfleura2
  ! Gradient calculated at Geom geometry
47 1 pfleura2
  REAL(KREAL), INTENT (OUT) :: gradcart(3*NAt)
48 1 pfleura2
49 1 pfleura2
  ! ======================================================================
50 1 pfleura2
51 1 pfleura2
  character(LCHARS) :: LINE
52 1 pfleura2
53 1 pfleura2
  logical           :: debug, G03Ok
54 1 pfleura2
  LOGICAL, SAVE :: first=.true.
55 1 pfleura2
56 2 pfleura2
  REAL(KREAL) :: Pi
57 1 pfleura2
58 1 pfleura2
  INTEGER(KINT) :: ItG03
59 2 pfleura2
  INTEGER(KINT) :: iat, i, n3at
60 2 pfleura2
  INTEGER(KINT) :: ITmp1, ITmp2
61 1 pfleura2
62 1 pfleura2
  CHARACTER(132) :: FileIn, FileOut, FileChk
63 1 pfleura2
64 1 pfleura2
  CHARACTER(3) :: SepIn=' < ', SepOut=' > '
65 2 pfleura2
  CHARACTER(VLCHARS), SAVE :: RunCommand
66 2 pfleura2
!  LOGICAL, SAVE :: FCopyRstrt=.False., FOrderChecked=.False.
67 1 pfleura2
68 1 pfleura2
  ! ======================================================================
69 1 pfleura2
70 1 pfleura2
  LOGICAL, EXTERNAL :: valid
71 1 pfleura2
72 1 pfleura2
  ! ======================================================================
73 1 pfleura2
74 1 pfleura2
  Pi=dacos(-1.0d0)
75 1 pfleura2
  n3at=3*nat
76 1 pfleura2
77 1 pfleura2
  debug=valid('EGRAD')
78 1 pfleura2
  if (debug) Call Header("Entering Egrad_gaussian")
79 1 pfleura2
80 1 pfleura2
  if (first) THEN
81 1 pfleura2
     First=.FALSE.
82 1 pfleura2
     call system("uname > Path.tmp")
83 1 pfleura2
     OPEN(IOTMP,FILE='Path.tmp')
84 1 pfleura2
     READ(IOTMP,'(A)') Line
85 1 pfleura2
     CLOSE(IOTMP)
86 1 pfleura2
     IF (index(Line,'CYGWIN').NE.0) THEN
87 1 pfleura2
        SepIn='   '
88 1 pfleura2
        SepOut='   '
89 1 pfleura2
     END IF
90 1 pfleura2
  END IF
91 1 pfleura2
92 1 pfleura2
  gradcart=0.
93 1 pfleura2
  E=0.
94 1 pfleura2
  FileIn=Trim(CalcName) // "." // Trim(ISuffix)
95 1 pfleura2
  FileOut=Trim(CalcName) // "." // Trim(OSuffix)
96 1 pfleura2
  FileChk=Trim(CalcName) // ".chk"
97 1 pfleura2
  RunCommand=Trim(ProgExe) // SepIn // Trim(FileIn) // SepOut // Trim(FileOut)
98 1 pfleura2
99 1 pfleura2
  IF (DEBUG) WRITE(*,*)'RunCommand:',TRIM(RunCommand)
100 1 pfleura2
101 1 pfleura2
  ! we create the input file
102 1 pfleura2
103 1 pfleura2
  OPEN(IOTMP,File=FileIn)
104 1 pfleura2
105 1 pfleura2
  Current => Gauss_root
106 1 pfleura2
  DO WHILE (ASSOCIATED(Current%next))
107 1 pfleura2
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
108 1 pfleura2
     WRITE(*,'(1X,A)') Trim(current%line)
109 1 pfleura2
     Current => current%next
110 1 pfleura2
  END DO
111 1 pfleura2
112 1 pfleura2
  WRITE(IOTMP,*)
113 1 pfleura2
114 1 pfleura2
  Current => Gauss_comment
115 1 pfleura2
  DO WHILE (ASSOCIATED(Current%next))
116 1 pfleura2
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
117 1 pfleura2
     Current => current%next
118 1 pfleura2
  END DO
119 1 pfleura2
  !  WRITE(IOOUT,"('Geometry ',I3,'/',I3,' for iteration ',I3)"),Igeom,NgeomF,Iopt
120 1 pfleura2
121 1 pfleura2
  WRITE(IOTMP,*)
122 1 pfleura2
  WRITE(IOTMP,*) Trim(Gauss_charge)
123 1 pfleura2
124 1 pfleura2
  DO I=1,Nat
125 1 pfleura2
     If (renum) THEN
126 1 pfleura2
        Iat=Order(I)
127 10 pfleura2
        WRITE(IOTMP,'(1X,A10,3(1X,F15.8),1X,A)') Trim(AtName(I)),GeomCart(Iat,:), TRIM(Gauss_Paste(I))
128 1 pfleura2
     ELSE
129 1 pfleura2
        Iat=OrderInv(I)
130 10 pfleura2
        WRITE(IOTMP,'(1X,A10,3(1X,F15.8),1X,A)') Trim(AtName(Iat)),GeomCart(I,:), TRIM(Gauss_Paste(Iat))
131 1 pfleura2
     END IF
132 1 pfleura2
  END DO
133 1 pfleura2
134 1 pfleura2
  WRITE(IOTMP,*)
135 1 pfleura2
136 1 pfleura2
  Current => Gauss_End
137 1 pfleura2
  DO WHILE (ASSOCIATED(Current%next))
138 1 pfleura2
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
139 1 pfleura2
     Current => current%next
140 1 pfleura2
  END DO
141 1 pfleura2
142 1 pfleura2
  WRITE(IOTMP,*)
143 1 pfleura2
  CLOSE(IOTMP)
144 1 pfleura2
145 1 pfleura2
  IF (debug) THEN
146 1 pfleura2
     WRITE(*,*) 'DBG EGRAD ' //  Trim(FileIn),' COORD=',TRIM(COORD)
147 1 pfleura2
     call system('cat ' // Trim(FileIn))
148 1 pfleura2
  END IF
149 1 pfleura2
150 1 pfleura2
!!! PFL 15th March 2008 ->
151 1 pfleura2
! Sometimes for unknown reasons G03 fails.
152 1 pfleura2
! We thus add one test to check that Gaussian has finisehd properly.
153 1 pfleura2
! We also check that we do not run an infinite loop...
154 1 pfleura2
155 1 pfleura2
 G03Ok=.FALSE.
156 1 pfleura2
 ItG03=0
157 1 pfleura2
158 1 pfleura2
  DO WHILE ((.NOT.G03Ok).AND.(ItG03<3))
159 1 pfleura2
   ItG03=ItG03+1
160 1 pfleura2
  call system(RunCommand)
161 1 pfleura2
 OPEN(IOTMP,FILE=FileOut, STATUS='old', POSITION='APPEND')
162 1 pfleura2
 BACKSPACE(IOTMP)
163 1 pfleura2
 READ(IOTMP,'(A)') Line
164 1 pfleura2
 IF (LINE(2:19).EQ.'Normal termination')  G03Ok=.TRUE.
165 1 pfleura2
  END DO
166 1 pfleura2
  CLOSE(IOTMP)
167 1 pfleura2
  IF (.NOT.G03Ok) THEN
168 1 pfleura2
     WRITE(*,*) "Egrad_gaussian Failed..."
169 1 pfleura2
     WRITE(*,*) "Wrong termination of Gaussian after 3 tries. Check Input and geometry"
170 1 pfleura2
     STOP
171 1 pfleura2
  END IF
172 1 pfleura2
173 1 pfleura2
  if (debug) WRITE(*,*) 'DBG EGRAD, back from calculation'
174 1 pfleura2
175 1 pfleura2
  ! Whatever the coordinate system, we read the cartesian gradient
176 1 pfleura2
  ! and we convert it to Zmat or other if needed
177 1 pfleura2
178 1 pfleura2
  OPEN(IOTMP,FILE=FileOut, STATUS='old')
179 1 pfleura2
  ! We first search for the forces
180 1 pfleura2
  READ(IOTMP,'(A)') LINE
181 1 pfleura2
  DO WHILE (INDEX(LINE,'Forces (Hartrees/Bohr)')==0)
182 1 pfleura2
     ! here, we have a problem, because there are so many ways to write E for Gaussian :-)
183 1 pfleura2
     ! but we do not really need E except if we want to weight the different points
184 1 pfleura2
     ! on the path... that will be done later :-)
185 1 pfleura2
     ! And I should use ConvGaussXmol ...
186 1 pfleura2
! PFL 3rd Jan 2008 ->
187 1 pfleura2
! I have finally upgraded the energy reading phase so that it should be able to read
188 1 pfleura2
! many formats corresponding to HF, DFT, MP2, AM1, PM3, ONIOM with or w/o PCM
189 1 pfleura2
190 1 pfleura2
! For MP2, energy is after the last =
191 1 pfleura2
     IF ((Line(2:9)=="E2 =    ")) THEN
192 1 pfleura2
      Itmp1=Index(LINE,"=",BACK=.TRUE.)+1
193 1 pfleura2
    READ(LINE(Itmp1:),*) e
194 1 pfleura2
      END IF
195 1 pfleura2
! For other methods, it is after the first =
196 1 pfleura2
     IF ((LINE(2:9)=='Energy= ').OR.(Line(2:9)=="SCF Done").OR.(Line(2:9)=="ONIOM: e") &
197 1 pfleura2
   .OR.(Line(2:9)==" with al") &
198 1 pfleura2
         .OR.(Line(2:31)=="Counterpoise: corrected energy")) THEN
199 1 pfleura2
      Itmp1=Index(LINE,"=")+1
200 1 pfleura2
    READ(LINE(Itmp1:),*) e
201 1 pfleura2
  END IF
202 1 pfleura2
! <- PFL 3 Jan 2008
203 1 pfleura2
     READ(IOTMP,'(A)') LINE
204 1 pfleura2
  END DO
205 1 pfleura2
  if (debug) WRITE(*,*) "GradCart reading - renum=",Renum
206 1 pfleura2
  READ(IOTMP,'(A)') LINE
207 1 pfleura2
  READ(IOTMP,'(A)') LINE
208 1 pfleura2
  DO I=1,Nat
209 1 pfleura2
     Iat=I
210 1 pfleura2
     IF (renum) Iat=Order(I)
211 1 pfleura2
     READ(IOTMP,*)  Itmp1,ITmp2, GradCart(3*Iat-2:3*Iat)
212 1 pfleura2
     if (debug) WRITE(*,*) "I,Iat,GradCart:",I,Iat,GradCart(3*Iat-2:3*Iat)
213 1 pfleura2
  END DO
214 1 pfleura2
215 1 pfleura2
! Gaussian gives the Forces in ua/a0, so we convert it into the
216 1 pfleura2
! gradient in ua/Angstrom
217 1 pfleura2
  gradCart=-1.0d0*gradCart*Unit
218 1 pfleura2
219 1 pfleura2
!  if (debug.AND.(COORD.EQ.'ZMAT')) THEN
220 1 pfleura2
!     DO WHILE (INDEX(LINE,'Internal Coordinate Forces')==0)
221 1 pfleura2
!        READ(IOTMP,'(A)') LINE
222 1 pfleura2
!!        WRITE(*,*) 'Pas bon:' // TRIM(LINE)
223 1 pfleura2
!     END DO
224 1 pfleura2
!     WRITE(*,*) TRIM(LINE)
225 1 pfleura2
!     DO I=1,Nat+2
226 1 pfleura2
!        READ(IOTMP,'(A)') LINE
227 1 pfleura2
!        WRITE(*,*) TRIM(LINE)
228 1 pfleura2
!     END DO
229 1 pfleura2
!  END IF
230 1 pfleura2
231 1 pfleura2
  CLOSE(IOTMP)
232 1 pfleura2
233 1 pfleura2
  if (debug) Call header("Egrad_gaussian Over")
234 1 pfleura2
235 1 pfleura2
  RETURN
236 1 pfleura2
237 2 pfleura2
!999 CONTINUE
238 2 pfleura2
!  if (.NOT.Ftmp) WRITE(*,*) 'We should not be here !!!!'
239 2 pfleura2
!  STOP
240 1 pfleura2
  ! ======================================================================
241 1 pfleura2
end subroutine egrad_gaussian