Statistiques
| Révision :

root / src / egrad_turbomole.f90 @ 2

Historique | Voir | Annoter | Télécharger (3,5 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
  use Path_module, only : Nat, AtName, unit,ProgExe,renum,order,OrderInv
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

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

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

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

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

    
35
  CHARACTER(3) :: SepIn=' ', SepOut=' '
36
  CHARACTER(VLCHARS), SAVE ::  RunCommand
37

    
38
  ! ======================================================================
39

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

    
47
  ! ======================================================================
48

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

    
52
  debug=valid('EGRAD')
53
  if (debug) WRITE(*,*) '================ Entering Egrad_TurboMole ===================='
54

    
55

    
56
  gradcart=0.
57
  E=0.
58

    
59
  FileIn="coord"
60
  FileOut="gradient"
61

    
62
  RunCommand=Trim(ProgExe)
63

    
64
  IF (DEBUG) WRITE(*,*)'RunCommand:',TRIM(RunCommand)
65

    
66
  ! we create the input file
67

    
68
  OPEN(IOTMP,File=FileIn)
69
  WRITE(IOTMP,'(1X,A)') '$coord'
70
  DO I=1,Nat
71
     If (renum) THEN
72
        Iat=Order(I)
73
        WRITE(IOTMP,'(1X,3(1X,F15.8),A5)') GeomCart(Iat,:)*Unit,Trim(AtName(Iat))
74
     ELSE
75
        Iat=OrderInv(I)
76
        WRITE(IOTMP,'(1X,3(1X,F15.8),A5)') GeomCart(I,:)*Unit,Trim(AtName(Iat))
77
     END IF
78
  END DO
79
  WRITE(IOTMP,'(1X,A)') '$user-defined bonds'
80
  WRITE(IOTMP,'(1X,A)') '$end'
81
  CLOSE(IOTMP)
82

    
83
  IF (debug) THEN
84
     WRITE(*,*) 'DBG EGRAD ' //  Trim(FileIn)
85
     call system('cat ' // Trim(FileIn))
86
  END IF
87

    
88

    
89
  call system(RunCommand)
90

    
91
  if (debug) WRITE(*,*) 'DBG EGRAD, back from calculation'
92

    
93
  ! Whatever the coordinate system, we read the cartesian gradient
94
  ! and we convert it to Zmat or other if needed
95

    
96
  OPEN(IOTMP,FILE=FileOut, STATUS='old')
97
! We check that gradient file is ok
98
  READ(IOTMP,'(A)') LINE 
99
  Line=AdjustL(Line)
100
  if (Line(1:5).NE.'$grad') THEN
101
     WRITE(*,*) "Error with Turbomole, gradient file does not start with $grad"
102
     STOP
103
  END IF
104

    
105
! we read the energy
106
  READ(IOTMP,'(A)') LINE
107
! energy is after the second = sign:
108
!  cycle =      1    SCF energy =    -2889.2212497430   |dE/dxyz| =  0.064137
109
  Idx=Index(Line,'=')
110
  Line=Line(Idx+1:)
111
  Idx=Index(Line,'=')
112
  Line=Line(Idx+1:)
113
 READ(Line,*) E
114

    
115
! We skip the coordinates
116
 DO I=1,Nat
117
    READ(IOTMP,'(A)') LINE
118
 END DO
119

    
120
! We read the gradient
121
  DO I=1,Nat
122
     Iat=I
123
     IF (renum) Iat=Order(I)
124
     READ(IOTMP,*)  GradCart(3*Iat-2:3*Iat)
125
     if (debug) WRITE(*,*) "I,Iat,GradCart:",I,Iat,GradCart(3*Iat-2:3*Iat)
126
  END DO
127

    
128
! TurboMole gives the Forces in au/a0, so we convert it into the 
129
! gradient in ua/Angstrom 
130
  gradCart=gradCart*unit
131

    
132
  CLOSE(IOTMP)
133

    
134
  if (debug) WRITE(*,*) '================  Egrad_TurboMole Over ===================='
135

    
136
  RETURN
137

    
138
999 CONTINUE
139
  WRITE(*,*) 'We should not be here !!!!'
140
  STOP
141
  ! ======================================================================
142
end subroutine egrad_TurboMole