Statistiques
| Révision :

root / src / egrad_turbomole.f90

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

1
subroutine egrad_turbomole(e,geomcart,gradcart)
2

    
3
  ! This routines calculates the energy and the gradient of 
4
  ! a molecule, using TurboMole 
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 : Nat, AtName, unit,ProgExe,renum,order,OrderInv
38
  use Io_module
39

    
40
  IMPLICIT NONE
41

    
42
  ! Energy (calculated if F300K=.F., else estimated)
43
  REAL(KREAL), INTENT (OUT) :: e
44
  ! Nb degree of freedom
45
  REAL(KREAL), INTENT (IN) :: geomcart(Nat,3)
46
  ! Gradient calculated at Geom geometry
47
  REAL(KREAL), INTENT (OUT) :: gradcart(3*NAt)
48

    
49
  ! ======================================================================
50

    
51
  character(LCHARS) :: LINE
52

    
53
  logical           :: debug
54

    
55

    
56
  REAL(KREAL) :: Pi
57

    
58
  INTEGER(KINT) :: iat, i, n3at
59
  INTEGER(KINT) :: Idx
60

    
61
  CHARACTER(132) :: FileIn, FileOut
62

    
63
!  CHARACTER(3) :: SepIn=' ', SepOut=' '
64
  CHARACTER(VLCHARS), SAVE ::  RunCommand
65

    
66
  ! ======================================================================
67

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

    
75
  ! ======================================================================
76

    
77
  Pi=dacos(-1.0d0)
78
  n3at=3*nat
79

    
80
  debug=valid('EGRAD')
81
  if (debug) WRITE(*,*) '================ Entering Egrad_TurboMole ===================='
82

    
83

    
84
  gradcart=0.
85
  E=0.
86

    
87
  FileIn="coord"
88
  FileOut="gradient"
89

    
90
  RunCommand=Trim(ProgExe)
91

    
92
  IF (DEBUG) WRITE(*,*)'RunCommand:',TRIM(RunCommand)
93

    
94
  ! we create the input file
95

    
96
  OPEN(IOTMP,File=FileIn)
97
  WRITE(IOTMP,'(1X,A)') '$coord'
98
  DO I=1,Nat
99
     If (renum) THEN
100
        Iat=Order(I)
101
        WRITE(IOTMP,'(1X,3(1X,F15.8),A5)') GeomCart(Iat,:)*Unit,Trim(AtName(Iat))
102
     ELSE
103
        Iat=OrderInv(I)
104
        WRITE(IOTMP,'(1X,3(1X,F15.8),A5)') GeomCart(I,:)*Unit,Trim(AtName(Iat))
105
     END IF
106
  END DO
107
  WRITE(IOTMP,'(1X,A)') '$user-defined bonds'
108
  WRITE(IOTMP,'(1X,A)') '$end'
109
  CLOSE(IOTMP)
110

    
111
  IF (debug) THEN
112
     WRITE(*,*) 'DBG EGRAD ' //  Trim(FileIn)
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 check that gradient file is ok
126
  READ(IOTMP,'(A)') LINE 
127
  Line=AdjustL(Line)
128
  if (Line(1:5).NE.'$grad') THEN
129
     WRITE(*,*) "Error with Turbomole, gradient file does not start with $grad"
130
     STOP
131
  END IF
132

    
133
! we read the energy
134
  READ(IOTMP,'(A)') LINE
135
! energy is after the second = sign:
136
!  cycle =      1    SCF energy =    -2889.2212497430   |dE/dxyz| =  0.064137
137
  Idx=Index(Line,'=')
138
  Line=Line(Idx+1:)
139
  Idx=Index(Line,'=')
140
  Line=Line(Idx+1:)
141
 READ(Line,*) E
142

    
143
! We skip the coordinates
144
 DO I=1,Nat
145
    READ(IOTMP,'(A)') LINE
146
 END DO
147

    
148
! We read the gradient
149
  DO I=1,Nat
150
     Iat=I
151
     IF (renum) Iat=Order(I)
152
     READ(IOTMP,*)  GradCart(3*Iat-2:3*Iat)
153
     if (debug) WRITE(*,*) "I,Iat,GradCart:",I,Iat,GradCart(3*Iat-2:3*Iat)
154
  END DO
155

    
156
! TurboMole gives the Forces in au/a0, so we convert it into the 
157
! gradient in ua/Angstrom 
158
  gradCart=gradCart*unit
159

    
160
  CLOSE(IOTMP)
161

    
162
  if (debug) WRITE(*,*) '================  Egrad_TurboMole Over ===================='
163

    
164
  RETURN
165

    
166
!999 CONTINUE
167
!  WRITE(*,*) 'We should not be here !!!!'
168
!  STOP
169
  ! ======================================================================
170
end subroutine egrad_TurboMole