Statistiques
| Révision :

root / src / egrad_LEPS.f90

Historique | Voir | Annoter | Télécharger (5,12 ko)

1 3 pfleura2
  SUBROUTINE egrad_LEPS(nat,e,geom,grad)
2 3 pfleura2
! This program computes the ernergy and gradien in cartesian coordinates
3 3 pfleura2
! for the cartesian geometry Geom
4 3 pfleura2
5 12 pfleura2
!----------------------------------------------------------------------
6 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
7 12 pfleura2
!  Centre National de la Recherche Scientifique,
8 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
9 12 pfleura2
!
10 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
11 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
12 12 pfleura2
!
13 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
14 12 pfleura2
!  Contact: optnpath@gmail.com
15 12 pfleura2
!
16 12 pfleura2
! This file is part of "Opt'n Path".
17 12 pfleura2
!
18 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
19 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
20 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
21 12 pfleura2
!  or (at your option) any later version.
22 12 pfleura2
!
23 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
24 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
25 12 pfleura2
!
26 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27 12 pfleura2
!  GNU Affero General Public License for more details.
28 12 pfleura2
!
29 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
30 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
31 12 pfleura2
!
32 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
33 12 pfleura2
! for commercial licensing opportunities.
34 12 pfleura2
!----------------------------------------------------------------------
35 12 pfleura2
36 3 pfleura2
   IMPLICIT NONE
37 3 pfleura2
     integer, parameter :: KINT = kind(1)
38 3 pfleura2
     integer, parameter :: KREAL = kind(1.0d0)
39 3 pfleura2
40 3 pfleura2
! Number of atoms
41 3 pfleura2
       INTEGER(KINT), INTENT(IN) :: Nat
42 3 pfleura2
! Input geometry
43 3 pfleura2
       REAL(KREAL), INTENT(IN) :: Geom(Nat,3)
44 3 pfleura2
! output energy and gradient
45 3 pfleura2
       REAL(KREAL), INTENT(OUT) :: E,grad(Nat*3)
46 3 pfleura2
47 3 pfleura2
48 3 pfleura2
! Parameters to define the surface
49 3 pfleura2
      INTEGER(KINT), DIMENSION(6), PARAMETER :: IECOEF = (/-1,9,-45,45,-9,1/)
50 3 pfleura2
      INTEGER(KINT), DIMENSION(6), PARAMETER :: ISCOEF = (/-3,-2,-1,1,2,3/)
51 3 pfleura2
      REAL(KREAL), PARAMETER :: hh=0.001d0
52 3 pfleura2
53 3 pfleura2
! Variables
54 8 pfleura2
       INTEGER(KINT) :: i,iat,jat
55 3 pfleura2
       REAL(KREAL), ALLOCATABLE :: Xyztmp(:,:),GradTmp(:,:)
56 8 pfleura2
57 3 pfleura2
       LOGICAL :: Debug
58 3 pfleura2
59 3 pfleura2
      REAL(KREAL), external :: ELEPS_xyz
60 3 pfleura2
61 3 pfleura2
62 3 pfleura2
  INTERFACE
63 3 pfleura2
     function valid(string) result (isValid)
64 3 pfleura2
       CHARACTER(*), intent(in) :: string
65 3 pfleura2
       logical                  :: isValid
66 3 pfleura2
     END function VALID
67 3 pfleura2
68 3 pfleura2
  END INTERFACE
69 3 pfleura2
70 3 pfleura2
  debug=valid('egrad_leps')
71 3 pfleura2
72 3 pfleura2
 if (debug) WRITE(*,*) '================ Entering Egrad_leps ==================='
73 3 pfleura2
 if (debug) THEN
74 3 pfleura2
    WRITE(*,*) "Cartesian Geometry"
75 3 pfleura2
    DO I=1,Nat
76 3 pfleura2
       WRITE(*,'(1X,I5,3(1X,F12.6))') I,Geom(i,1:3)
77 3 pfleura2
    END DO
78 3 pfleura2
 END IF
79 3 pfleura2
80 3 pfleura2
      ALLOCATE(XyZTmp(Nat,3),GradTmp(Nat,3))
81 3 pfleura2
82 3 pfleura2
      e=ELEPS_xyz(nat,Geom)
83 3 pfleura2
84 3 pfleura2
! We now calculate the gradients using numerical derivatives
85 3 pfleura2
      Grad=0.d0
86 3 pfleura2
      GradTmp=0.d0
87 3 pfleura2
      do iat=1,3
88 3 pfleura2
         do jat=1,nat
89 3 pfleura2
            xyztmp=geom
90 3 pfleura2
            do i=1,6
91 3 pfleura2
               xyztmp(jat,iat)=geom(jat,iat)+ISCoef(i)*hh
92 3 pfleura2
               gradTmp(jat,iat)=gradTmp(jat,iat)+IECoef(i)*ELEPS_xyz(nat,xyztmp)
93 3 pfleura2
            end do
94 3 pfleura2
         end do
95 3 pfleura2
      end do
96 3 pfleura2
      gradTmp=gradTmp/(60.*hh)
97 3 pfleura2
      do iat=1,nat
98 3 pfleura2
       grad(3*iat-2:3*iat)=gradTmp(iat,1:3)
99 3 pfleura2
      end do
100 3 pfleura2
101 3 pfleura2
 if (debug) THEN
102 3 pfleura2
    WRITE(*,*) "Cartesian gradient "
103 3 pfleura2
    DO I=1,Nat
104 3 pfleura2
       WRITE(*,'(1X,I5,3(1X,F12.6))') I,Gradtmp(i,1:3)
105 3 pfleura2
    END DO
106 3 pfleura2
 END IF
107 3 pfleura2
108 3 pfleura2
109 3 pfleura2
      deallocate(xyztmp,gradTmp)
110 3 pfleura2
111 3 pfleura2
112 3 pfleura2
 if (debug) WRITE(*,*) '================ Exiting Egrad_leps ==================='
113 3 pfleura2
114 3 pfleura2
! ======================================================================
115 3 pfleura2
      end
116 3 pfleura2
117 3 pfleura2
118 3 pfleura2
119 3 pfleura2
      function ELEPS_xyz(natoms,Xyz)
120 3 pfleura2
121 3 pfleura2
        use Path_module, only : order
122 8 pfleura2
        use Io_module, only : au2ev
123 3 pfleura2
124 3 pfleura2
   IMPLICIT NONE
125 3 pfleura2
     integer, parameter :: KINT = kind(1)
126 3 pfleura2
     integer, parameter :: KREAL = kind(1.0d0)
127 3 pfleura2
128 3 pfleura2
129 3 pfleura2
      INTEGER(KINT) ,INTENT(IN) :: natoms
130 3 pfleura2
      REAL(KREAL) ,INTENT(IN) :: Xyz(natoms,3)
131 3 pfleura2
      REAL(KREAL) :: ELEPS_xyz
132 3 pfleura2
133 3 pfleura2
      INTEGER(KINT) :: i
134 3 pfleura2
      REAL(KREAL) :: rAB, rBC, rAC
135 3 pfleura2
136 3 pfleura2
      REAL(KREAL), PARAMETER :: a=0.05, b=0.30, c=0.05
137 3 pfleura2
      REAL(KREAL), PARAMETER :: dAB=4.746, dBC=4.747, dAC=3.445
138 3 pfleura2
      REAL(KREAL), PARAMETER :: r0=0.742, alpha=1.942
139 3 pfleura2
140 3 pfleura2
      REAL(KREAL) :: Qbc,QAc,Qab,Jab,Jbc,Jac
141 3 pfleura2
142 3 pfleura2
      rAB=0.
143 3 pfleura2
      rAC=0.
144 3 pfleura2
      rBC=0.
145 3 pfleura2
      do i=1,3
146 3 pfleura2
         rBC=rBC+(xyz(Order(3),i)-xyz(order(2),i))**2
147 3 pfleura2
         rAB=rAB+(xyz(order(1),i)-xyz(order(2),i))**2
148 3 pfleura2
         rAC=rAC+(xyz(order(1),i)-xyz(order(3),i))**2
149 3 pfleura2
      end do
150 3 pfleura2
      rAB=sqrt(rAB)
151 3 pfleura2
      rBC=sqrt(rBC)
152 3 pfleura2
      rAC=sqrt(rAC)
153 3 pfleura2
154 3 pfleura2
! For consistency with previous articles : rAC is constrained to be 3.742
155 3 pfleura2
      rAC=3.742
156 3 pfleura2
157 3 pfleura2
      Qab = dab*(1.5*exp(-2*alpha*(rAB-r0))-exp(-alpha*(rAB-r0)))/(2+2*a)
158 3 pfleura2
      Qbc = dbc*(1.5*exp(-2*alpha*(rBC-r0))-exp(-alpha*(rBC-r0)))/(2+2*b)
159 3 pfleura2
      Qac = dac*(1.5*exp (-2*alpha*(rAC-r0))-exp(-alpha*(rAC-r0)))/(2+2*c)
160 3 pfleura2
      Jab = dab*(exp(-2*alpha*(rAB-r0))-6*exp(-alpha*(rAB-r0)))/(4+4*a)
161 3 pfleura2
      Jbc = dbc*(exp(-2*alpha*(rBC-r0))-6*exp(-alpha*(rBC-r0)))/(4+4*b)
162 3 pfleura2
      Jac = dac*(exp(-2*alpha*(rAC-r0))-6*exp(-alpha*(rAC-r0)))/(4+4*c)
163 3 pfleura2
164 3 pfleura2
! V(x,y) = Qab(x)+Qbc(y)+Qac(rac)-sqrt(Jab(x)**2+Jbc(y)**2+Jac(x)**2-Jab(x)*Jbc(y)-Jbc(y)*Jac(rac)-Jab(x)*Jac(rac))
165 3 pfleura2
166 3 pfleura2
167 8 pfleura2
      ELEPS_xyz=(Qab+Qbc+Qac-sqrt(Jab**2+Jbc**2+Jac**2-Jab*Jbc-Jbc*Jac-Jab*Jac))/au2eV
168 3 pfleura2
169 3 pfleura2
      return
170 3 pfleura2
    end function ELEPS_xyz