Statistiques
| Révision :

root / src / egrad_mopac.f90 @ 4

Historique | Voir | Annoter | Télécharger (4,71 ko)

1
subroutine egrad_mopac(e,geomcart,gradcart)
2

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

    
6
  use Path_module, only : Nat, renum,Order,OrderInv,AtName, Coord, dzdc, indzmat,Nom,Atome, massat, unit,ProgExe, au2kcal
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
23
  LOGICAL, SAVE :: first=.true.
24

    
25
  REAL(KREAL), ALLOCATABLE :: GradTmp(:)
26

    
27
  REAL(KREAL) :: d, a_val, Pi
28

    
29
  REAL(KREAL) :: coef,x
30
  INTEGER(KINT) :: iat, jat, kat, i, j, k,n3at
31
  INTEGER(KINT) :: ITmp1,ITmp2, Idx
32
  INTEGER(KINT), PARAMETER :: IOLOG=12, IOCOM=11
33

    
34
  CHARACTER(132) :: FileIn, FileOut, FileChk
35

    
36
  CHARACTER(3) :: SepIn=' < ', SepOut=' > '
37
  CHARACTER(VLCHARS), SAVE ::  RunCommand
38

    
39
  ! ======================================================================
40

    
41
  INTERFACE
42
     function valid(string) result (isValid)
43
       CHARACTER(*), intent(in) :: string
44
       logical                  :: isValid
45
     END function VALID
46
  END INTERFACE
47

    
48
  ! ======================================================================
49

    
50
  Pi=dacos(-1.0d0)
51
  n3at=3*nat
52

    
53
  debug=valid('EGRAD')
54
  if (debug) WRITE(*,*) '================ Entering Egrad_Mopac ===================='
55

    
56
  if (first) THEN
57
     First=.FALSE.
58
     SepIn='   '
59
     SepOut='   '
60
  END IF
61
 
62
  gradcart=0.
63
  E=0.
64

    
65
  FileIn=Trim(CalcName) // "." // Trim(ISuffix)
66
  FileOut=Trim(CalcName) // "." // Trim(OSuffix)
67
  FileChk=Trim(CalcName) // ".arc"
68

    
69
  RunCommand=Trim(ProgExe) // SepIn // Trim(FileIn) 
70

    
71
  IF (DEBUG) WRITE(*,*)'RunCommand:',TRIM(RunCommand)
72

    
73
  ! we create the input file
74

    
75
  OPEN(IOTMP,File=FileIn)
76
  WRITE(IOTMP,'(A)') '* All comments are put at the begining of the file'
77
  Current => Mopac_comment
78
  DO WHILE (ASSOCIATED(Current%next))
79
     WRITE(IOTMP,'(A)') Trim(current%line)
80
     Current => current%next
81
  END DO
82

    
83
  Current => Mopac_root
84
  DO WHILE (ASSOCIATED(Current%next))
85
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
86
     WRITE(*,'(1X,A)') Trim(current%line)
87
     Current => current%next
88
  END DO
89

    
90
  DO I=1,Nat
91
     If (renum) THEN
92
        Iat=Order(I)
93
        WRITE(IOTMP,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomCart(Iat,:)
94
     ELSE
95
        Iat=OrderInv(I)
96
        WRITE(IOTMP,'(1X,A10,3(1X,F15.8))') Trim(AtName(Iat)),GeomCart(I,:)
97
     END IF
98
  END DO
99

    
100
     WRITE(IOTMP,'(1X,A)') Trim(Mopac_EndGeom)
101

    
102
  Current => Mopac_End
103
  DO WHILE (ASSOCIATED(Current%next))
104
     WRITE(IOTMP,'(1X,A)') Trim(current%line)
105
     Current => current%next
106
  END DO
107

    
108
  WRITE(IOTMP,*) 
109
  CLOSE(IOTMP)
110

    
111
  IF (debug) THEN
112
     WRITE(*,*) 'DBG EGRAD ' //  Trim(FileIn),' COORD=',TRIM(COORD)
113
     call system('cat ' // Trim(FileIn))
114
  END IF
115

    
116

    
117
  call system(RunCommand)
118

    
119
  if (debug) WRITE(*,*) 'DBG EGRAD, back from calculation'
120

    
121
  ! Whatever the coordinate system, we read the cartesian gradient
122
  ! and we convert it to Zmat or other if needed
123

    
124
  OPEN(IOTMP,FILE=FileOut, STATUS='old')
125
  ! We first search for the forces
126
  READ(IOTMP,'(A)') LINE
127

    
128
  DO WHILE (INDEX(LINE,'FINAL  POINT  AND  DERIVATIVES')==0)
129
     IF (INDEX(Line,'FINAL HEAT OF FORMATION').NE.0)  THEN
130
        Itmp1=Index(Line,"=")+1
131
        ITmp2=Index(Line,"KCAL")-1
132
        Read(Line(Itmp1:Itmp2),*) E
133
        E=E/au2kcal
134
     END IF
135
     READ(IOTMP,'(A)',END=999) LINE
136
  END DO
137

    
138
  if (debug) WRITE(*,*) "GradCart reading - renum=",Renum
139
  READ(IOTMP,'(A)') LINE
140
  READ(IOTMP,'(A)') LINE
141
  DO I=1,Nat
142
     Iat=I
143
     IF (renum) Iat=Order(I)
144
     DO J=1,3
145
        READ(IOTMP,'(A)') Line
146
! Gradient is on the 7th column
147
        DO K=1,6
148
           Line=AdjustL(Line)
149
           Idx=Index(Line," ")
150
           Line=AdjustL(Line(Idx+1:))
151
        END DO
152
        READ(Line,*) GradCart(3*Iat-3+j)
153
     END DO
154
     if (debug) WRITE(*,*) "I,Iat,GradCart:",I,Iat,GradCart(3*Iat-2:3*Iat)
155
  END DO
156

    
157
! Mopac gives the Forces in kcal/angstrom, so we convert it into the 
158
! gradient in ua/Angstrom 
159
  gradCart=gradCart/au2kcal
160

    
161
!  if (debug.AND.(COORD.EQ.'ZMAT')) THEN
162
!     DO WHILE (INDEX(LINE,'Internal Coordinate Forces')==0)
163
!        READ(IOTMP,'(A)') LINE
164
!!        WRITE(*,*) 'Pas bon:' // TRIM(LINE)
165
!     END DO
166
!     WRITE(*,*) TRIM(LINE)
167
!     DO I=1,Nat+2
168
!        READ(IOTMP,'(A)') LINE
169
!        WRITE(*,*) TRIM(LINE)
170
!     END DO
171
!  END IF
172

    
173
  CLOSE(IOTMP)
174

    
175
  if (debug) WRITE(*,*) '================  Egrad_Mopac Over ===================='
176

    
177
  RETURN
178

    
179
999 CONTINUE
180
  WRITE(*,*) 'We should not be here !!!!'
181
  STOP
182
  ! ======================================================================
183
end subroutine egrad_mopac