root / src / Egrad.f90
Historique | Voir | Annoter | Télécharger (18,41 ko)
1 | 1 | pfleura2 | subroutine Egrad(E,Geom,Grad,NCoord,IGeom,IOpt,GeomCart,FOptGeom,GeomOld,GeomCart_old) |
---|---|---|---|
2 | 1 | pfleura2 | |
3 | 1 | pfleura2 | ! This routines calculates the energy E and the gradient Grad of |
4 | 1 | pfleura2 | ! a molecule with Geometry Geom (may be in internal coordinates), |
5 | 1 | pfleura2 | ! using for now, either Gaussian or Ext, more general later. |
6 | 1 | pfleura2 | |
7 | 12 | pfleura2 | !---------------------------------------------------------------------- |
8 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
9 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
10 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
11 | 12 | pfleura2 | ! |
12 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
13 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
14 | 12 | pfleura2 | ! |
15 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
16 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
17 | 12 | pfleura2 | ! |
18 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
19 | 12 | pfleura2 | ! |
20 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
21 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
22 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
23 | 12 | pfleura2 | ! or (at your option) any later version. |
24 | 12 | pfleura2 | ! |
25 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
26 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
27 | 12 | pfleura2 | ! |
28 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
29 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
30 | 12 | pfleura2 | ! |
31 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
32 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
33 | 12 | pfleura2 | ! |
34 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
35 | 12 | pfleura2 | ! for commercial licensing opportunities. |
36 | 12 | pfleura2 | !---------------------------------------------------------------------- |
37 | 12 | pfleura2 | |
38 | 8 | pfleura2 | use Path_module, only : Nat,AtName,Coord,dzdc,indzmat,Atome,massat, & |
39 | 8 | pfleura2 | prog,NCart,XyzGeomF, XyzGeomI, renum, & |
40 | 1 | pfleura2 | GeomOld_all,BTransInvF,BTransInv_local,UMatF,UMat_local & |
41 | 8 | pfleura2 | , BprimT,ScanCoord, Coordinate,NPrim,BMat_BakerT,BBT,BBT_inv & |
42 | 10 | pfleura2 | ,Order, OrderInv, XPrimitiveF,FPBC,XGeomRefPBC,YGeomRefPBC,ZGeomRefPBC |
43 | 1 | pfleura2 | |
44 | 1 | pfleura2 | ! IntCoordF(NGeomF,NCoord),GeomOld_all(NGeomF,NCoord) |
45 | 1 | pfleura2 | ! allocated in Path.f90 |
46 | 1 | pfleura2 | |
47 | 1 | pfleura2 | use Io_module |
48 | 1 | pfleura2 | IMPLICIT NONE |
49 | 1 | pfleura2 | |
50 | 1 | pfleura2 | ! Energy (calculated if F300K=.F., else estimated) |
51 | 1 | pfleura2 | REAL(KREAL), INTENT (OUT) :: E |
52 | 1 | pfleura2 | ! NCoord: Number of the degrees of freedom |
53 | 1 | pfleura2 | ! IGeom: index of the geometry. |
54 | 1 | pfleura2 | INTEGER(KINT), INTENT (IN) :: NCoord, IGeom, IOpt |
55 | 1 | pfleura2 | ! Geometry at which gradient is calculated (cf Factual also): |
56 | 1 | pfleura2 | REAL(KREAL), INTENT (INOUT) :: Geom(NCoord) |
57 | 1 | pfleura2 | ! Gradient calculated at Geom geometry: |
58 | 1 | pfleura2 | REAL(KREAL), INTENT (OUT) :: Grad(NCoord) |
59 | 1 | pfleura2 | ! Cartesian geometry corresponding to (Internal Geometry) Geom: |
60 | 1 | pfleura2 | REAL(KREAL), INTENT (OUT) :: GeomCart(Nat,3) |
61 | 1 | pfleura2 | !!! Optional, just for geometry optimization with Baker coordinates |
62 | 1 | pfleura2 | REAL(KREAL), INTENT (IN), OPTIONAL :: GeomCart_old(Nat,3) |
63 | 1 | pfleura2 | REAL(KREAL), INTENT (INOUT), OPTIONAL :: GeomOld(NCoord) |
64 | 1 | pfleura2 | ! FOptGeom is a flag indicating if we are doing a geom optimization |
65 | 1 | pfleura2 | ! it can be omitted so that we use a local flag: Flag_Opt_Geom |
66 | 1 | pfleura2 | LOGICAL,INTENT (IN), OPTIONAL :: FOptGeom |
67 | 1 | pfleura2 | ! if FOptGeom is given Flag_Opt_Geom=FOptGeom, else Flag_Opt_Geom=F |
68 | 1 | pfleura2 | LOGICAL :: Flag_Opt_Geom |
69 | 1 | pfleura2 | |
70 | 1 | pfleura2 | ! ====================================================================== |
71 | 1 | pfleura2 | |
72 | 1 | pfleura2 | LOGICAL :: debug |
73 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: GradTmp(:) |
74 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: GradCart(:) |
75 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: x(:), y(:), z(:) |
76 | 1 | pfleura2 | REAL(KREAL) :: Pi |
77 | 10 | pfleura2 | REAL(KREAL) :: MRot(3,3), Rmsd |
78 | 1 | pfleura2 | |
79 | 1 | pfleura2 | INTEGER(KINT) :: iat, i, j, IBeg,Idx |
80 | 1 | pfleura2 | |
81 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: XPrimRef(:), XPrim(:) ! NPrim |
82 | 1 | pfleura2 | |
83 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
84 | 1 | pfleura2 | ! |
85 | 1 | pfleura2 | !!!!!!!! PFL Debug |
86 | 1 | pfleura2 | ! |
87 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
88 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: GeomTmp(:,:) !3,Nat |
89 | 1 | pfleura2 | LOGICAL :: FALOBBT,FALOBPrimt,FAloBBTInv |
90 | 1 | pfleura2 | LOGICAL :: DebugPFL |
91 | 1 | pfleura2 | |
92 | 1 | pfleura2 | ! ====================================================================== |
93 | 1 | pfleura2 | INTERFACE |
94 | 1 | pfleura2 | function valid(string) result (isValid) |
95 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
96 | 1 | pfleura2 | logical :: isValid |
97 | 1 | pfleura2 | END function VALID |
98 | 1 | pfleura2 | END INTERFACE |
99 | 1 | pfleura2 | ! ====================================================================== |
100 | 1 | pfleura2 | |
101 | 1 | pfleura2 | Pi=dacos(-1.0d0) |
102 | 1 | pfleura2 | |
103 | 1 | pfleura2 | if (present(FOptGeom)) THEN |
104 | 1 | pfleura2 | Flag_Opt_Geom=FOptGeom |
105 | 1 | pfleura2 | ELSE |
106 | 1 | pfleura2 | Flag_Opt_Geom=.FALSE. |
107 | 1 | pfleura2 | END IF |
108 | 1 | pfleura2 | |
109 | 1 | pfleura2 | debug=valid('EGRAD') |
110 | 1 | pfleura2 | debugPFL=valid('bakerPFL') |
111 | 1 | pfleura2 | if (debug) Call Header("Entering Egrad") |
112 | 1 | pfleura2 | |
113 | 1 | pfleura2 | if (debug) Print *, 'EGrad.f90, L73, IOpt=', IOpt, ' Flag_Opt_Geom=',Flag_Opt_Geom |
114 | 1 | pfleura2 | |
115 | 1 | pfleura2 | Grad=0. |
116 | 1 | pfleura2 | E=0. |
117 | 1 | pfleura2 | |
118 | 1 | pfleura2 | |
119 | 1 | pfleura2 | ALLOCATE(GradCart(3*Nat)) |
120 | 1 | pfleura2 | ALLOCATE(x(Nat),y(Nat),z(Nat)) |
121 | 1 | pfleura2 | ALLOCATE(XPrimRef(NPrim),XPrim(NPrim)) |
122 | 1 | pfleura2 | |
123 | 1 | pfleura2 | SELECT CASE (COORD) |
124 | 1 | pfleura2 | CASE ('ZMAT') |
125 | 1 | pfleura2 | ! In order to avoid problem with numbering and linear angles/diehedral, we convert the |
126 | 1 | pfleura2 | ! zmat into cartesian coordinates |
127 | 1 | pfleura2 | Call Int2Cart(nat,indzmat,Geom,GeomCart) |
128 | 10 | pfleura2 | ! In case of PBC calculations, we have to re-orient the geometry onto the user initial geometry |
129 | 10 | pfleura2 | If (FPBC) THEN |
130 | 10 | pfleura2 | ! we align this geometry on the initial one |
131 | 10 | pfleura2 | if (debug) THEN |
132 | 10 | pfleura2 | WRITe(*,*) "We are orientating..." |
133 | 10 | pfleura2 | WRITE(*,*) "Geom before orientation" |
134 | 10 | pfleura2 | WRITE(*,*) Nat |
135 | 10 | pfleura2 | WRITE(*,*) "" |
136 | 10 | pfleura2 | DO I=1,Nat |
137 | 10 | pfleura2 | If (renum) Iat=Order(I) |
138 | 10 | pfleura2 | WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomCart(I,1),GeomCart(I,2),GeomCart(I,3) |
139 | 10 | pfleura2 | END DO |
140 | 10 | pfleura2 | END IF |
141 | 10 | pfleura2 | |
142 | 10 | pfleura2 | IF (Renum) THEN |
143 | 10 | pfleura2 | DO I=1,Nat |
144 | 10 | pfleura2 | Iat=Order(I) |
145 | 10 | pfleura2 | X(I)=GeomCart(Iat,1) |
146 | 10 | pfleura2 | Y(I)=GeomCart(Iat,2) |
147 | 10 | pfleura2 | Z(I)=GeomCart(Iat,3) |
148 | 10 | pfleura2 | END DO |
149 | 10 | pfleura2 | ELSE |
150 | 10 | pfleura2 | X(1:Nat)=GeomCart(1:Nat,1) |
151 | 10 | pfleura2 | Y(1:Nat)=GeomCart(1:Nat,2) |
152 | 10 | pfleura2 | Z(1:Nat)=GeomCart(1:Nat,3) |
153 | 10 | pfleura2 | END IF |
154 | 10 | pfleura2 | |
155 | 11 | pfleura2 | if (debug) then |
156 | 10 | pfleura2 | WRITE(*,*) "Geom before orientation after reorderring" |
157 | 10 | pfleura2 | WRITE(*,*) Nat |
158 | 10 | pfleura2 | WRITE(*,*) "" |
159 | 10 | pfleura2 | DO I=1,Nat |
160 | 10 | pfleura2 | ! Iat=I |
161 | 10 | pfleura2 | ! If (Renum) Iat=Order(I) |
162 | 10 | pfleura2 | WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)),X(I),Y(I),Z(I) |
163 | 10 | pfleura2 | END DO |
164 | 10 | pfleura2 | WRITE(*,*) "Ref Geom" |
165 | 10 | pfleura2 | WRITE(*,*) Nat |
166 | 10 | pfleura2 | WRITE(*,*) "" |
167 | 10 | pfleura2 | DO I=1,Nat |
168 | 10 | pfleura2 | WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)),XGeomRefPBC(I),YGeomRefPBC(I),ZGeomRefPBC(I) |
169 | 10 | pfleura2 | END DO |
170 | 10 | pfleura2 | END IF |
171 | 10 | pfleura2 | |
172 | 10 | pfleura2 | Call CalcRmsd(Nat,XGeomRefPBC,YGeomRefPBC,ZGeomRefPBC, & |
173 | 10 | pfleura2 | X,Y,Z, MRot, Rmsd,.TRUE.,.TRUE.) |
174 | 10 | pfleura2 | |
175 | 10 | pfleura2 | If (DEBUG) THEN |
176 | 10 | pfleura2 | WRITE(*,*) "Geom AFTER orientation" |
177 | 10 | pfleura2 | WRITE(*,*) Nat |
178 | 10 | pfleura2 | WRITE(*,*) "" |
179 | 10 | pfleura2 | DO I=1,Nat |
180 | 10 | pfleura2 | WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(I)),X(I),Y(I),Z(I) |
181 | 10 | pfleura2 | END DO |
182 | 10 | pfleura2 | END IF |
183 | 10 | pfleura2 | |
184 | 10 | pfleura2 | If (Renum) THEN |
185 | 10 | pfleura2 | Do I=1,Nat |
186 | 10 | pfleura2 | Iat=orderInv(I) |
187 | 10 | pfleura2 | GeomCart(Iat,1)=X(I) |
188 | 10 | pfleura2 | GeomCart(Iat,2)=Y(I) |
189 | 10 | pfleura2 | GeomCart(Iat,3)=Z(I) |
190 | 10 | pfleura2 | END DO |
191 | 10 | pfleura2 | END IF |
192 | 11 | pfleura2 | END IF |
193 | 11 | pfleura2 | |
194 | 1 | pfleura2 | CASE ('BAKER') |
195 | 1 | pfleura2 | XPrimRef=XPrimitiveF(IGeom,:) |
196 | 1 | pfleura2 | IF (Flag_Opt_Geom) THEN |
197 | 1 | pfleura2 | IF (IOpt .EQ. 1) THEN |
198 | 1 | pfleura2 | GeomCart(:,1) = XyzGeomI(IGeom,1,:) |
199 | 1 | pfleura2 | GeomCart(:,2) = XyzGeomI(IGeom,2,:) |
200 | 1 | pfleura2 | GeomCart(:,3) = XyzGeomI(IGeom,3,:) |
201 | 1 | pfleura2 | ELSE |
202 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Before Call ConvertBakerInternal_cart; L125, Egrad.f90' |
203 | 1 | pfleura2 | if (.NOT.present(GeomOld)) THEN |
204 | 1 | pfleura2 | WRITE(*,*) "ERROR: GeomOld not passed as an argument" |
205 | 1 | pfleura2 | STOP |
206 | 1 | pfleura2 | END IF |
207 | 1 | pfleura2 | WRITE(*,*) 'GeomOld=' |
208 | 1 | pfleura2 | WRITE(*,'(12(1X,F6.3))') GeomOld |
209 | 1 | pfleura2 | WRITE(*,*) 'Geom=' |
210 | 1 | pfleura2 | WRITE(*,'(12(1X,F6.3))') Geom |
211 | 1 | pfleura2 | if (.NOT.present(GeomCart_Old)) THEN |
212 | 1 | pfleura2 | WRITE(*,*) "ERROR: GeomCart_Old not passed as an argument" |
213 | 1 | pfleura2 | STOP |
214 | 1 | pfleura2 | END IF |
215 | 1 | pfleura2 | |
216 | 1 | pfleura2 | WRITE(*,*) 'GeomCart_old=' |
217 | 1 | pfleura2 | WRITE(*,'(20(1X,F6.3))') GeomCart_old(1:Nat,1:3) |
218 | 1 | pfleura2 | Call ConvertBakerInternal_cart(GeomOld,Geom,GeomCart_old(:,1), & |
219 | 1 | pfleura2 | GeomCart_old(:,2),GeomCart_old(:,3),x,y,z,XPrim,XPrimRef) |
220 | 1 | pfleura2 | GeomCart(:,1) = x(:) |
221 | 1 | pfleura2 | GeomCart(:,2) = y(:) |
222 | 1 | pfleura2 | GeomCart(:,3) = z(:) |
223 | 1 | pfleura2 | END IF |
224 | 1 | pfleura2 | ELSE |
225 | 1 | pfleura2 | IF (IOpt .EQ. 0) THEN |
226 | 1 | pfleura2 | GeomCart(:,1) = XyzGeomF(IGeom,1,:) |
227 | 1 | pfleura2 | GeomCart(:,2) = XyzGeomF(IGeom,2,:) |
228 | 1 | pfleura2 | GeomCart(:,3) = XyzGeomF(IGeom,3,:) |
229 | 1 | pfleura2 | ELSE |
230 | 1 | pfleura2 | ! IntCoordF(NGeomF,NCoord), XyzGeomF(NGeomF,3,Nat) |
231 | 1 | pfleura2 | ! Geom has to be converted into x,y,z |
232 | 1 | pfleura2 | ! GeomOld_all and XyzGeomF are old geometry in internal and cartesian coords resp. |
233 | 1 | pfleura2 | DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart() |
234 | 1 | pfleura2 | BTransInv_local(I,:) = BTransInvF(IGeom,I,:) |
235 | 1 | pfleura2 | UMat_local(:,I) = UMatF(IGeom,:,I) |
236 | 1 | pfleura2 | END DO |
237 | 1 | pfleura2 | if (debug) Print *, 'I am before Call ConvertBakerInternal_cart; L160, Egrad.f90' |
238 | 1 | pfleura2 | WRITE(*,*) 'GeomOld=' |
239 | 1 | pfleura2 | WRITE(*,'(12(1X,F6.3))') GeomOld_all(IGeom,:) |
240 | 1 | pfleura2 | WRITE(*,*) 'Geom=' |
241 | 1 | pfleura2 | WRITE(*,'(12(1X,F6.3))') Geom |
242 | 1 | pfleura2 | WRITE(*,*) 'DBG Egrad L165 GeomCart_old=' |
243 | 1 | pfleura2 | DO I=1,Nat |
244 | 1 | pfleura2 | WRITE(*,'(3(1X,F12.8))') XyzGeomF(IGeom,:,I) |
245 | 1 | pfleura2 | END DO |
246 | 1 | pfleura2 | |
247 | 1 | pfleura2 | Call ConvertBakerInternal_cart(GeomOld_all(IGeom,:),Geom,XyzGeomF(IGeom,1,:), & |
248 | 1 | pfleura2 | XyzGeomF(IGeom,2,:),XyzGeomF(IGeom,3,:),x,y,z,XPrim,XPrimRef) |
249 | 1 | pfleura2 | if (debug) Print *, 'I am after Call ConvertBakerInternal_cart; L111, Egrad.f90' |
250 | 1 | pfleura2 | DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart() |
251 | 1 | pfleura2 | BTransInvF(IGeom,I,:) = BTransInv_local(I,:) |
252 | 1 | pfleura2 | END DO |
253 | 1 | pfleura2 | ! GeomCart is actually XyzCoord and has INTENT(OUT) in this subroutine. |
254 | 1 | pfleura2 | GeomCart(:,1) = x(:) |
255 | 1 | pfleura2 | GeomCart(:,2) = y(:) |
256 | 1 | pfleura2 | GeomCart(:,3) = z(:) |
257 | 1 | pfleura2 | END IF ! matches IF (IOpt .EQ. 0) THEN |
258 | 1 | pfleura2 | END IF |
259 | 1 | pfleura2 | CASE ('MIXED') |
260 | 1 | pfleura2 | ! write(*,*) "Coucou 4-mixed" |
261 | 1 | pfleura2 | Call Mixed2Cart(Nat,indzmat,geom,GeomCart) |
262 | 1 | pfleura2 | CASE ('CART') |
263 | 5 | pfleura2 | |
264 | 1 | pfleura2 | GeomCart=reshape(Geom,(/Nat,3/)) |
265 | 5 | pfleura2 | if (debug) THEN |
266 | 5 | pfleura2 | WRITE(*,*) "Coord=CART... in egrad" |
267 | 5 | pfleura2 | DO Iat=1,Nat |
268 | 5 | pfleura2 | WRITE(IOTMP,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),Geom(3*Iat-2:3*Iat) |
269 | 5 | pfleura2 | END DO |
270 | 5 | pfleura2 | END IF |
271 | 1 | pfleura2 | CASE ('HYBRID') |
272 | 1 | pfleura2 | ! write(*,*) "Coucou 4-hybrid" |
273 | 1 | pfleura2 | GeomCart=reshape(Geom,(/Nat,3/)) |
274 | 1 | pfleura2 | CASE DEFAULT |
275 | 1 | pfleura2 | WRITE (*,*) "Coord=",TRIM(COORD)," not recognized. Stop" |
276 | 1 | pfleura2 | STOP |
277 | 1 | pfleura2 | END SELECT |
278 | 1 | pfleura2 | !WRITE(*,*) Nat |
279 | 1 | pfleura2 | !WRITE(*,*) 'GeomCart in Egrad_baker' |
280 | 1 | pfleura2 | !DO I=1,Nat |
281 | 1 | pfleura2 | ! WRITE(*,'(1X,A,3(1X,F12.8))') AtName(I),GeomCart(I,1:3) |
282 | 1 | pfleura2 | !END DO |
283 | 1 | pfleura2 | |
284 | 10 | pfleura2 | |
285 | 10 | pfleura2 | |
286 | 1 | pfleura2 | SELECT CASE (Prog) |
287 | 1 | pfleura2 | CASE ('GAUSSIAN') |
288 | 1 | pfleura2 | ! we call the Gaussian routine. |
289 | 1 | pfleura2 | ! it will return the energy and the gradient in cartesian coordinates. |
290 | 1 | pfleura2 | ! Gradient calculated at GeomCart geometry and stored in GradCart, which has INTENT(OUT) |
291 | 1 | pfleura2 | Call egrad_gaussian(E,GeomCart,GradCart) |
292 | 1 | pfleura2 | CASE ('MOPAC') |
293 | 1 | pfleura2 | ! we call the Mopac routine. |
294 | 1 | pfleura2 | ! it will return the energy and the gradient in cartesian coordinates. |
295 | 1 | pfleura2 | ! Gradient calculated at GeomCart geometry and stored in GradCart, which has INTENT(OUT) |
296 | 1 | pfleura2 | Call egrad_mopac(E,GeomCart,GradCart) |
297 | 1 | pfleura2 | CASE ('VASP') |
298 | 1 | pfleura2 | Call egrad_vasp(E,Geomcart,GradCart) |
299 | 5 | pfleura2 | CASE ('SIESTA') |
300 | 5 | pfleura2 | Call egrad_siesta(E,Geomcart,GradCart) |
301 | 1 | pfleura2 | CASE ('TURBOMOLE') |
302 | 1 | pfleura2 | Call egrad_turbomole(E,Geomcart,GradCart) |
303 | 1 | pfleura2 | CASE ('EXT') |
304 | 1 | pfleura2 | Call egrad_ext(E,Geomcart,GradCart) |
305 | 1 | pfleura2 | CASE ('TEST') |
306 | 1 | pfleura2 | Call egrad_test(Nat,E,Geomcart,GradCart) |
307 | 5 | pfleura2 | CASE ('TEST2D') |
308 | 5 | pfleura2 | Call egrad_test_2D(Nat,E,Geomcart,GradCart) |
309 | 12 | pfleura2 | ! Chamfre is not public. Contact Wei.Dong@ens-lyon.fr |
310 | 12 | pfleura2 | ! and optnpath@gmail.com if you want it. |
311 | 12 | pfleura2 | ! CASE ('CHAMFRE') |
312 | 12 | pfleura2 | ! Call egrad_chamfre(Nat,E,Geomcart,GradCart) |
313 | 4 | pfleura2 | CASE ('LEPS') |
314 | 4 | pfleura2 | Call egrad_LEPS(Nat,E,Geomcart,GradCart) |
315 | 1 | pfleura2 | END SELECT |
316 | 1 | pfleura2 | if (debug) THEN |
317 | 1 | pfleura2 | WRITE(*,*) 'DBG EGRAD, GradCart read' |
318 | 1 | pfleura2 | DO I=1,Nat |
319 | 1 | pfleura2 | Iat=I |
320 | 1 | pfleura2 | if (renum) Iat=orderInv(I) |
321 | 1 | pfleura2 | WRITE(*,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GradCart(3*I-2:3*I) |
322 | 1 | pfleura2 | END DO |
323 | 1 | pfleura2 | END IF |
324 | 1 | pfleura2 | |
325 | 1 | pfleura2 | ! If (PROG=="VASP") STOP |
326 | 1 | pfleura2 | |
327 | 1 | pfleura2 | |
328 | 1 | pfleura2 | ! We have the gradient in Cartesian coordinates... which is ok for COORD=Cart, Hybrid |
329 | 1 | pfleura2 | ! but we have to convert it into Zmat if COORD=Zmat |
330 | 1 | pfleura2 | SELECT CASE (COORD) |
331 | 1 | pfleura2 | CASE ("ZMAT") |
332 | 1 | pfleura2 | ALLOCATE(GradTmp(3*Nat)) |
333 | 1 | pfleura2 | if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_int" |
334 | 1 | pfleura2 | CALL CalcBMat_int (nat, reshape(GeomCart,(/3,Nat/),ORDER=(/2,1/)), indzmat, dzdc, massat,atome) |
335 | 1 | pfleura2 | |
336 | 1 | pfleura2 | if (debug) WRITE(*,*) "DBG EGRAD Calling ConvGrad_Cart2Int" |
337 | 1 | pfleura2 | CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp) |
338 | 1 | pfleura2 | |
339 | 1 | pfleura2 | if (debug) WRITE(*,*) "DBG EGRAD Storing Grad" |
340 | 1 | pfleura2 | Grad(1)=GradTmp(4) |
341 | 1 | pfleura2 | Grad(2)=GradTmp(7) |
342 | 1 | pfleura2 | ! We might have troubles whith angles that are not in the [0:pi] range because, |
343 | 1 | pfleura2 | ! when converted to catesian coord, they do appear in the [0:Pi] range to gaussian... |
344 | 1 | pfleura2 | ! so that the derivative is not good, and a multiplicative factor should be added... |
345 | 1 | pfleura2 | ! |
346 | 1 | pfleura2 | ! This in fact should be taken care of in B mat calculation... |
347 | 1 | pfleura2 | ! |
348 | 1 | pfleura2 | IF ((Geom(3).LE.0).OR.(Geom(3).GE.Pi)) THEN |
349 | 1 | pfleura2 | Grad(3)=-1.0d0*GradTmp(8) |
350 | 1 | pfleura2 | ELSE |
351 | 1 | pfleura2 | Grad(3)=GradTmp(8) |
352 | 1 | pfleura2 | END IF |
353 | 1 | pfleura2 | Idx=4 |
354 | 1 | pfleura2 | DO I=4,Nat |
355 | 1 | pfleura2 | Grad(Idx)=GradTmp(3*i-2) |
356 | 1 | pfleura2 | Grad(Idx+1)=GradTmp(3*i-1) |
357 | 1 | pfleura2 | Grad(Idx+2)=GradTmp(3*i) |
358 | 1 | pfleura2 | Idx=Idx+3 |
359 | 1 | pfleura2 | END DO |
360 | 1 | pfleura2 | DEALLOCATE(GradTmp) |
361 | 1 | pfleura2 | CASE ('BAKER') |
362 | 1 | pfleura2 | ! We have the gradient in Cartesian coordinates... which is ok for COORD=Cart, Hybrid |
363 | 1 | pfleura2 | ! but we have to convert it into internal coordinates if COORD=Baker |
364 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!! |
365 | 1 | pfleura2 | ! |
366 | 1 | pfleura2 | ! PFL Debug |
367 | 1 | pfleura2 | ! |
368 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!! |
369 | 1 | pfleura2 | if (debugPFL) THEN |
370 | 1 | pfleura2 | WRITE(*,*) "DBG PFL Egrad_Baker... computing dzdc" |
371 | 1 | pfleura2 | if (.not.ALLOCATED(indzmat)) THEN |
372 | 1 | pfleura2 | ALLOCATE(indzmat(Nat,5)) |
373 | 1 | pfleura2 | IndZmat=0 |
374 | 1 | pfleura2 | Indzmat(1,1)=1 |
375 | 1 | pfleura2 | IndZmat(2,1)=2 |
376 | 1 | pfleura2 | IndZmat(2,2)=1 |
377 | 1 | pfleura2 | IndZmat(3,1)=3 |
378 | 1 | pfleura2 | IndZmat(3,2)=2 |
379 | 1 | pfleura2 | IndZmat(3,3)=1 |
380 | 1 | pfleura2 | IndZmat(4,1)=4 |
381 | 1 | pfleura2 | IndZmat(4,2)=3 |
382 | 1 | pfleura2 | IndZmat(4,3)=2 |
383 | 1 | pfleura2 | IndZmat(4,4)=1 |
384 | 1 | pfleura2 | END IF |
385 | 1 | pfleura2 | IF (.NOT.ALLOCATED(DzDc)) THEN |
386 | 1 | pfleura2 | ALLOCATE(DzDc(3,nat,3,Nat)) |
387 | 1 | pfleura2 | END IF |
388 | 1 | pfleura2 | if (.NOT.Allocated(GeomTmp)) Allocate(GeomTmp(3,Nat)) |
389 | 1 | pfleura2 | DO I=1,Nat |
390 | 1 | pfleura2 | GeomTmp(1,I)=GeomCart(OrderInv(I),1) |
391 | 1 | pfleura2 | GeomTmp(2,I)=GeomCart(OrderInv(i),2) |
392 | 1 | pfleura2 | GeomTmp(3,I)=GeomCart(OrderInv(i),3) |
393 | 1 | pfleura2 | END DO |
394 | 1 | pfleura2 | |
395 | 1 | pfleura2 | DzDc=0.d0 |
396 | 1 | pfleura2 | CALL CalcBMat_int (nat, GeomTmp, indzmat, dzdc, massat,atome) |
397 | 1 | pfleura2 | |
398 | 1 | pfleura2 | END IF ! if (debugPFL) |
399 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!!! |
400 | 1 | pfleura2 | ! Debugging PFL |
401 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!! |
402 | 1 | pfleura2 | |
403 | 1 | pfleura2 | WRITE(*,*) "BTransInv_local Trans that is used originally" |
404 | 1 | pfleura2 | DO J=1,3*Nat |
405 | 1 | pfleura2 | WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J) |
406 | 1 | pfleura2 | END DO |
407 | 1 | pfleura2 | |
408 | 1 | pfleura2 | WRITE(*,*) "Calculating actual values using GeomCart" |
409 | 1 | pfleura2 | if (.NOT.Allocated(GeomTmp)) Allocate(GeomTmp(3,Nat)) |
410 | 1 | pfleura2 | GeomTmp(1,:)=GeomCart(1:Nat,1) |
411 | 1 | pfleura2 | GeomTmp(2,:)=GeomCart(1:Nat,2) |
412 | 1 | pfleura2 | GeomTmp(3,:)=GeomCart(1:Nat,3) |
413 | 1 | pfleura2 | |
414 | 1 | pfleura2 | ! Computing B^prim: |
415 | 1 | pfleura2 | FAloBBT=.NOT.ALLOCATED(BBT) |
416 | 1 | pfleura2 | FAloBBTInv=.NOT.ALLOCATED(BBT_inv) |
417 | 1 | pfleura2 | FAloBPrimT=.NOT.ALLOCATED(BprimT) |
418 | 1 | pfleura2 | if (FAloBPrimT) ALLOCATE(Bprimt(3*Nat,NPrim)) |
419 | 1 | pfleura2 | if (FAloBBT) ALLOCATE(BBt(NCoord,NCoord)) |
420 | 1 | pfleura2 | if (FAloBBTInv) ALLOCATE(BBt_inv(NCoord,NCoord)) |
421 | 1 | pfleura2 | BprimT=0.d0 |
422 | 1 | pfleura2 | ScanCoord=>Coordinate |
423 | 1 | pfleura2 | I=0 |
424 | 1 | pfleura2 | DO WHILE (Associated(ScanCoord%next)) |
425 | 1 | pfleura2 | I=I+1 |
426 | 1 | pfleura2 | SELECT CASE (ScanCoord%Type) |
427 | 1 | pfleura2 | CASE ('BOND') |
428 | 1 | pfleura2 | CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2,GeomTmp,BprimT(1,I)) |
429 | 1 | pfleura2 | CASE ('ANGLE') |
430 | 1 | pfleura2 | CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,GeomTmp,BprimT(1,I)) |
431 | 1 | pfleura2 | CASE ('DIHEDRAL') |
432 | 1 | pfleura2 | CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,ScanCoord%At4,GeomTmp,BprimT(1,I)) |
433 | 1 | pfleura2 | END SELECT |
434 | 1 | pfleura2 | ScanCoord => ScanCoord%next |
435 | 1 | pfleura2 | END DO |
436 | 1 | pfleura2 | |
437 | 1 | pfleura2 | if (debug) THEN |
438 | 1 | pfleura2 | WRITE(*,*) "Bprim " |
439 | 1 | pfleura2 | DO J=1,3*Nat |
440 | 1 | pfleura2 | WRITE(*,'(50(1X,F12.6))') BprimT(J,:) |
441 | 1 | pfleura2 | END DO |
442 | 1 | pfleura2 | END IF |
443 | 1 | pfleura2 | |
444 | 1 | pfleura2 | BMat_BakerT = 0.d0 |
445 | 1 | pfleura2 | DO I=1,NCoord |
446 | 1 | pfleura2 | DO J=1,NPrim |
447 | 1 | pfleura2 | !BprimT is transpose of B^prim. |
448 | 1 | pfleura2 | !B = UMat^T B^prim, B^T = (B^prim)^T UMat |
449 | 1 | pfleura2 | BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat_local(J,I) |
450 | 1 | pfleura2 | END DO |
451 | 1 | pfleura2 | END DO |
452 | 1 | pfleura2 | |
453 | 1 | pfleura2 | BBT = 0.d0 |
454 | 1 | pfleura2 | DO I=1,NCoord |
455 | 1 | pfleura2 | DO J=1,3*Nat ! BBT(:,I) forms BB^T |
456 | 1 | pfleura2 | BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I) |
457 | 1 | pfleura2 | END DO |
458 | 1 | pfleura2 | END DO |
459 | 1 | pfleura2 | |
460 | 1 | pfleura2 | BBT_inv = 0.d0 |
461 | 1 | pfleura2 | |
462 | 1 | pfleura2 | Call GenInv(NCoord,BBT,BBT_inv,NCoord) |
463 | 1 | pfleura2 | |
464 | 1 | pfleura2 | !Print *, 'BBT_inv=' |
465 | 1 | pfleura2 | DO J=1,NCoord |
466 | 1 | pfleura2 | ! WRITE(*,'(50(1X,F10.2))') BBT_inv(:,J) |
467 | 1 | pfleura2 | ! Print *, BBT_inv(:,J) |
468 | 1 | pfleura2 | END DO |
469 | 1 | pfleura2 | !Print *, 'End of BBT_inv' |
470 | 1 | pfleura2 | |
471 | 1 | pfleura2 | ! Calculation of (B^T)^-1 = (BB^T)^-1B: |
472 | 1 | pfleura2 | BTransInv_local = 0.d0 |
473 | 1 | pfleura2 | DO I=1,3*Nat |
474 | 1 | pfleura2 | DO J=1,NCoord |
475 | 1 | pfleura2 | BTransInv_local(:,I)=BTransInv_local(:,I)+BBT_inv(:,J)*BMat_BakerT(I,J) |
476 | 1 | pfleura2 | END DO |
477 | 1 | pfleura2 | END DO |
478 | 1 | pfleura2 | |
479 | 1 | pfleura2 | Print *, 'BMat_BakerT=' |
480 | 1 | pfleura2 | DO J=1,3*Nat |
481 | 1 | pfleura2 | WRITE(*,'(50(1X,F12.8))') BMat_BakerT(:,J) |
482 | 1 | pfleura2 | END DO |
483 | 1 | pfleura2 | |
484 | 1 | pfleura2 | WRITE(*,*) "BTransInv_local Trans corresponding to GeomCart" |
485 | 1 | pfleura2 | DO J=1,3*Nat |
486 | 1 | pfleura2 | WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J) |
487 | 1 | pfleura2 | END DO |
488 | 1 | pfleura2 | |
489 | 1 | pfleura2 | if (FAloBPrimT) DEALLOCATE(Bprimt) |
490 | 1 | pfleura2 | if (FAloBBT) DEALLOCATE(BBt) |
491 | 1 | pfleura2 | if (FAloBBTInv) DEALLOCATE(BBt_inv) |
492 | 1 | pfleura2 | |
493 | 1 | pfleura2 | Grad=0.d0 |
494 | 1 | pfleura2 | DO I=1, 3*Nat |
495 | 1 | pfleura2 | ! Here Grad is gradient in Baker coordinates. GradCart(3*Nat) |
496 | 1 | pfleura2 | Grad(:) = Grad(:) + BTransInv_local(:,I)*GradCart(I) !BTransInv_local = BTransInv in Opt_Geom.f90 |
497 | 1 | pfleura2 | END DO |
498 | 1 | pfleura2 | !WRITE(*,*) 'In Egrad.f90, L263, Gradient:' |
499 | 1 | pfleura2 | !WRITE(*,'(12(1X,F8.4))') Grad(1:NCoord) |
500 | 1 | pfleura2 | |
501 | 1 | pfleura2 | |
502 | 1 | pfleura2 | CASE ('MIXED') |
503 | 1 | pfleura2 | ALLOCATE(GradTmp(3*Nat)) |
504 | 1 | pfleura2 | if (debug) WRITE(*,*) "DBG EGRAD Calling CalcBMat_mixed" |
505 | 1 | pfleura2 | CALL CalcBMat_mixed (nat, reshape(GeomCart,(/3,Nat/),ORDER=(/2,1/)), indzmat, dzdc, massat,atome) |
506 | 1 | pfleura2 | |
507 | 1 | pfleura2 | if (Debug) THEN |
508 | 1 | pfleura2 | WRITE(*,*) "DzDc" |
509 | 1 | pfleura2 | DO I=1,Nat |
510 | 1 | pfleura2 | DO J=1,3 |
511 | 1 | pfleura2 | WRITE(*,'(50(1X,F12.6))') dzdc(J,I,:,:) |
512 | 1 | pfleura2 | END DO |
513 | 1 | pfleura2 | END DO |
514 | 1 | pfleura2 | END IF |
515 | 1 | pfleura2 | |
516 | 1 | pfleura2 | |
517 | 1 | pfleura2 | CALL ConvGrad_Cart2Int(Nat,dzdc,IndZmat,GradCart,GradTmp) |
518 | 1 | pfleura2 | DO I=1,Nat |
519 | 1 | pfleura2 | WRITE(*,'(1X,3(1X,F10.5))') GradTmp(3*I-2:3*I) |
520 | 1 | pfleura2 | END DO |
521 | 1 | pfleura2 | SELECT CASE (NCART) |
522 | 1 | pfleura2 | CASE (1) |
523 | 1 | pfleura2 | Grad(1:3)=GradTmp(1:3) |
524 | 1 | pfleura2 | Grad(4)=GradTmp(4) |
525 | 1 | pfleura2 | Grad(5)=GradTmp(7) |
526 | 1 | pfleura2 | Grad(6)=GradTmp(8) |
527 | 1 | pfleura2 | Idx=7 |
528 | 1 | pfleura2 | IBeg=4 |
529 | 1 | pfleura2 | CASE(2) |
530 | 1 | pfleura2 | Grad(1:3)=GradTmp(1:3) |
531 | 1 | pfleura2 | Grad(4:6)=GradTmp(4:6) |
532 | 1 | pfleura2 | Grad(7)=GradTmp(7) |
533 | 1 | pfleura2 | Grad(8)=GradTmp(8) |
534 | 1 | pfleura2 | Idx=9 |
535 | 5 | pfleura2 | IBeg=4 |
536 | 1 | pfleura2 | CASE DEFAULT |
537 | 1 | pfleura2 | Idx=1 |
538 | 1 | pfleura2 | IBeg=1 |
539 | 1 | pfleura2 | END SELECT |
540 | 1 | pfleura2 | DO I=IBeg,Nat |
541 | 1 | pfleura2 | Grad(Idx)=GradTmp(3*i-2) |
542 | 1 | pfleura2 | Grad(Idx+1)=GradTmp(3*i-1) |
543 | 1 | pfleura2 | Grad(Idx+2)=GradTmp(3*i) |
544 | 1 | pfleura2 | Idx=Idx+3 |
545 | 1 | pfleura2 | END DO |
546 | 1 | pfleura2 | DEALLOCATE(GradTmp) |
547 | 1 | pfleura2 | CASE ("CART","HYBRID") |
548 | 9 | pfleura2 | Grad=GradCart |
549 | 1 | pfleura2 | CASE DEFAULT |
550 | 1 | pfleura2 | WRITE(*,*) "Coord=",AdjustL(Trim(COORD))," not yet implemented in Egradients. STOP" |
551 | 1 | pfleura2 | STOP |
552 | 1 | pfleura2 | END SELECT |
553 | 1 | pfleura2 | |
554 | 1 | pfleura2 | DEALLOCATE(GradCart) |
555 | 1 | pfleura2 | DEALLOCATE(x,y,z) |
556 | 1 | pfleura2 | |
557 | 1 | pfleura2 | IF (Debug) WRITE(*,*) 'DBG EGRAD grad',grad(1:NCoord) |
558 | 1 | pfleura2 | if (debug) Call Header("Egrad Over") |
559 | 1 | pfleura2 | |
560 | 1 | pfleura2 | !999 CONTINUE |
561 | 1 | pfleura2 | !if (.NOT.Ftmp) WRITE(*,*) 'We should not be here !!!!' |
562 | 1 | pfleura2 | !STOP |
563 | 1 | pfleura2 | ! ====================================================================== |
564 | 1 | pfleura2 | end subroutine Egrad |