root / src / Path_module.f90
Historique | Voir | Annoter | Télécharger (14,94 ko)
1 |
MODULE Path_module |
---|---|
2 |
! This module contains most of the variables needed for the path |
3 |
|
4 |
!---------------------------------------------------------------------- |
5 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
6 |
! Centre National de la Recherche Scientifique, |
7 |
! Université Claude Bernard Lyon 1. All rights reserved. |
8 |
! |
9 |
! This work is registered with the Agency for the Protection of Programs |
10 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
11 |
! |
12 |
! Authors: P. Fleurat-Lessard, P. Dayal |
13 |
! Contact: optnpath@gmail.com |
14 |
! |
15 |
! This file is part of "Opt'n Path". |
16 |
! |
17 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
18 |
! it under the terms of the GNU Affero General Public License as |
19 |
! published by the Free Software Foundation, either version 3 of the License, |
20 |
! or (at your option) any later version. |
21 |
! |
22 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
23 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
24 |
! |
25 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
26 |
! GNU Affero General Public License for more details. |
27 |
! |
28 |
! You should have received a copy of the GNU Affero General Public License |
29 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
30 |
! |
31 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
32 |
! for commercial licensing opportunities. |
33 |
!---------------------------------------------------------------------- |
34 |
|
35 |
use VarTypes |
36 |
|
37 |
IMPLICIT NONE |
38 |
|
39 |
SAVE |
40 |
|
41 |
INTEGER(KINT), PARAMETER :: NMaxL=21 |
42 |
INTEGER(KINT), PARAMETER :: Max_Z=86 |
43 |
INTEGER(KINT), PARAMETER :: MaxFroz=100 |
44 |
REAL(KREAL), PARAMETER :: a0=0.529177249d0 |
45 |
REAL(KREAL), PARAMETER :: Unit=1.d0/a0 |
46 |
REAL(KREAL), PARAMETER :: Ang2au=a0, Au2Ang=Unit |
47 |
REAL(KREAL) :: Pi |
48 |
|
49 |
! Frozen contains the indices of frozen atoms |
50 |
INTEGER(KINT),ALLOCATABLE :: Frozen(:) !Nat |
51 |
! Cart contains the indices of atoms described in cartesian coords |
52 |
INTEGER(KINT),ALLOCATABLE :: Cart(:) !Nat |
53 |
! intFroz is the number of internal coord frozen |
54 |
! NFroz the number of frozen atoms |
55 |
! Ncart the number of atoms described in cartesian coords |
56 |
INTEGER(KINT) :: IntFroz, NFroz, NCart |
57 |
! FrozAtoms is true for a frozen atom, false else. |
58 |
LOGICAL, ALLOCATABLE :: FrozAtoms(:) !! Nat |
59 |
! Number of Primitives (mainly for Baker coordinates) |
60 |
INTEGER(KINT) :: NPrim |
61 |
! Nat number of atoms |
62 |
INTEGER(KINT) :: Nat |
63 |
! NGeomI number of initial geometries |
64 |
! NgeomF number of final geometries |
65 |
INTEGER(KINT) :: NGeomI, NGeomF |
66 |
! NCoord=3*Nat or NFree depending on the coordinate choice |
67 |
INTEGER(KINT) :: NCoord |
68 |
INTEGER(KINT) :: NMaxPtPath=1000 |
69 |
! IReparam is the period of reparameterization of the Path |
70 |
INTEGER(KINT) :: IReparam=1 |
71 |
! IReparamT is the period of reparameterization of the tangents along the path |
72 |
! Be default IReparamT=IReparam |
73 |
INTEGER(KINT) :: IReparamT |
74 |
! ISpline is the iteration number where spline interpolation starts to be used |
75 |
! instead of linear interpolation |
76 |
INTEGER(KINT) :: ISpline=1 |
77 |
! Linear: if TRUE, then we perform linear interpolation and not spline |
78 |
LOGICAL :: Linear |
79 |
|
80 |
! FrozTol is the criterion to decide wether a frozen atom has moved between |
81 |
! two initial geometries |
82 |
REAL(KREAL) :: FrozTol=1e-4 |
83 |
|
84 |
! BoxTol is the criterion to decide wether an atom has crossed the box between |
85 |
! two initial geometries |
86 |
REAL(KREAL) :: BoxTol=0.5 |
87 |
|
88 |
LOGICAL :: Freq, MW, Bohr, Renum, Hinv |
89 |
! OptReac: if TRUE the reactants will be optimized. Default is FALSE |
90 |
LOGICAL :: OptReac |
91 |
! OptProd: if TRUE the products will be optimized. Default is FALSE |
92 |
LOGICAL :: OptProd |
93 |
! PathOnly: if TRUE, only the initial path will be constructed. |
94 |
! Default is FALSE, that is OpenPath construct the path and optimize it |
95 |
LOGICAL :: PathOnly |
96 |
! CalcEReac: if TRUE the reactants energy will be computed. Default is FALSE |
97 |
! Not compatible with RunMode=Para |
98 |
LOGICAL :: CalcEReac |
99 |
! CalEProd: if TRUE the products energy will be computed. Default is FALSE |
100 |
! Not compatible with RunMode=Para |
101 |
LOGICAL :: CalcEProd |
102 |
! AnaGeom: if TRUE the geometries are analyzed |
103 |
LOGICAL :: AnaGeom |
104 |
! Name of the file to analyse geometries |
105 |
CHARACTER(LCHARS) :: AnaFile |
106 |
! Name of the Gplot file to see the path evolution |
107 |
CHARACTER(LCHARS) :: GplotFile |
108 |
! Nb: number of variables to monitor, including Centers of Mass |
109 |
INTEGER(KINT) :: Nb |
110 |
! NbVar: number of geometrical variables to monitor |
111 |
INTEGER(KINT) :: NbVar |
112 |
! NbCom: number of center of mass to create |
113 |
INTEGER(KINT) :: NbCom |
114 |
TYPE(ListCoord), POINTER :: GeomList,CurVar |
115 |
TYPE(Barycenter), POINTER :: Bary,CurBary |
116 |
! Format to print the values |
117 |
CHARACTER(VLCHARS) :: FormAna |
118 |
! Factor to use to print the values |
119 |
REAL(KREAL), ALLOCATABLE :: PrintGeomFactor(:) ! NbVar |
120 |
! How to update the Hessian |
121 |
LOGICAL :: IniHup,HupNeighbour |
122 |
|
123 |
REAL(KREAL) :: Fact,FTan |
124 |
! IGeomRef is the index of the reference geometry, used to calculate the Zmat |
125 |
! or the Baker coordinates. |
126 |
INTEGER(KINT) :: IGeomRef=-1 |
127 |
! For geometry optimization , OptGeom is the index of the starting geometry |
128 |
INTEGER(KINT) :: OptGeom=-1 |
129 |
|
130 |
! Optimization parameter |
131 |
INTEGER(KINT) :: MaxCyc |
132 |
REAL(KREAL) :: SThresh, Smax, SthreshRms |
133 |
REAL(KREAL) :: GThresh, GThreshRMS |
134 |
! Name of the file to print geometries and their energies |
135 |
CHARACTER(LCHARS) :: GeomFile |
136 |
! Flag to decide if we print something in GeomFile |
137 |
LOGICAL :: FPrintGeom |
138 |
|
139 |
! Number of steps in memory for Step_RFO_all |
140 |
INTEGER(KINT) :: NGintMax = 10 |
141 |
|
142 |
CHARACTER(SCHARS) :: Coord='HYBRID' |
143 |
CHARACTER(SCHARS) :: Step_method='RFO' |
144 |
CHARACTER(SCHARS) :: Prog="GAUSSIAN" |
145 |
CHARACTER(VLCHARS) :: ProgExe="g03" |
146 |
! Input: format of the geometry input |
147 |
! PFL 2013/02: This name is dumb ! I should have used GeomFormat ! => To DO!! |
148 |
CHARACTER(SCHARS) :: Input |
149 |
! Poscar: is the name to use for POSCAR files for VASP |
150 |
CHARACTER(SCHARS) :: Poscar |
151 |
|
152 |
! PFL 06/2011: HesUpd is deprecated |
153 |
! I replace it by HUpdate that is more intuitive to me |
154 |
CHARACTER(SCHARS) :: hesupd="BFGS" |
155 |
! HUpdate indicates which method to use for updating the Hessian or its inverse |
156 |
CHARACTER(SCHARS) :: HUpdate="BFGS" |
157 |
|
158 |
REAL(KREAL), ALLOCATABLE, TARGET :: XyzGeomI(:,:,:) ! (NGeomI,3,Nat) |
159 |
REAL(KREAL), ALLOCATABLE :: XyzGeomF(:,:,:) ! (NGeomF,3,Nat) |
160 |
REAL(KREAL), ALLOCATABLE :: XyzTangent(:,:) ! (NGeomF,3*Nat) |
161 |
REAL(KREAL), ALLOCATABLE :: IntTangent(:,:) ! (NGeomF,Nfree=3Nat-6) |
162 |
REAL(KREAL), ALLOCATABLE :: IntCoordI(:,:) ! (NGeomI,3*Nat-6) |
163 |
! IntCoordF: Final Internal coordinates for number of final geometries. |
164 |
! 3*Nat-6 is the number of coordinates (NCoord) of each geometry. |
165 |
REAL(KREAL), ALLOCATABLE :: IntCoordF(:,:) ! (NGeomF,3*Nat-6) |
166 |
REAL(KREAL), ALLOCATABLE :: Vfree(:,:) ! (Ncoord,Ncoord) |
167 |
REAL(KREAL), ALLOCATABLE :: SGeom(:) ! (NGeomF) |
168 |
REAL(KREAL), ALLOCATABLE :: Energies(:) ! NGeomF |
169 |
! NCoord=3*Nat or NFree depending on the coordinate choice |
170 |
REAL(KREAL), ALLOCATABLE :: Grad(:,:) ! (NGeomF,NCoord) |
171 |
REAL(KREAL), ALLOCATABLE :: Hess(:,:,:) !(NgeomF, N,N) |
172 |
REAL(KREAL), ALLOCATABLE :: DzDc(:,:,:,:) ! (3,Nat,3,Nat) |
173 |
REAL(KREAL), ALLOCATABLE :: BMat_BakerT(:,:) ! (3*Nat,NCoord) |
174 |
INTEGER(KINT), ALLOCATABLE :: IndZmat(:,:) ! (Nat,5) |
175 |
INTEGER(KINT), ALLOCATABLE :: Order(:),OrderInv(:) ! Nat |
176 |
CHARACTER(10), ALLOCATABLE :: AtName(:) ! Nat |
177 |
INTEGER(KINT), ALLOCATABLE :: Atome(:) ! Nat |
178 |
REAL(KREAL), ALLOCATABLE :: MassAt(:) ! Nat |
179 |
REAL(KREAL), ALLOCATABLE :: BTransInv(:,:) ! BTransInv (3*Nat-6,3*Nat), used for Baker case. |
180 |
REAL(KREAL), ALLOCATABLE :: BTransInvF(:,:,:) ! BTransInvF (NGeomF,3*Nat-6,3*Nat) |
181 |
! BTransInv_local (3*Nat-6,3*Nat), used for Baker case in Opt_Geom.f90 |
182 |
REAL(KREAL), ALLOCATABLE :: BTransInv_local(:,:) |
183 |
REAL(KREAL), ALLOCATABLE :: UMat(:,:) !(NPrim,3*Nat-6) |
184 |
REAL(KREAL), ALLOCATABLE :: UMat_local(:,:) !(NPrim,3*Nat-6) |
185 |
REAL(KREAL), ALLOCATABLE :: UMatF(:,:,:) !(NGeomF,NPrim,3*Nat-6) |
186 |
!REAL(KREAL), ALLOCATABLE :: IntCoordIBaker(:,:) ! (NGeomI,NCoord=3*Nat-6) |
187 |
! IntCoordIBaker allocated in PathCreate.f90 |
188 |
REAL(KREAL), ALLOCATABLE :: Xprimitive(:,:) ! Xprimitive(NgeomI,NPrim) |
189 |
REAL(KREAL), ALLOCATABLE :: Xprimitive_t(:) ! used in ConvertBakerInternal_cart.f as a temporary variable. |
190 |
REAL(KREAL), ALLOCATABLE :: XprimitiveF(:,:) ! Xprimitive(NgeomF,NPrim) |
191 |
REAL(KREAL), ALLOCATABLE :: GeomOld_all(:,:) |
192 |
REAL(KREAL), ALLOCATABLE :: GeomOld(:) ! Used in DIIS step method. |
193 |
|
194 |
LOGICAL, PARAMETER :: FRot=.TRUE., FAlign=.TRUE. |
195 |
REAL(KREAL), ALLOCATABLE :: BprimT(:,:) !(3*Nat,NPrim). This is B^prim. |
196 |
REAL(KREAL), ALLOCATABLE :: BBT(:,:) ! BBT (3*Nat-6,3*Nat-6), used for Baker case |
197 |
REAL(KREAL), ALLOCATABLE :: BBT_inv(:,:) ! BBT_inv (3*Nat-6,3*Nat-6), used for Baker case |
198 |
INTEGER(KINT) :: Symmetry_elimination |
199 |
LOGICAL :: FirstTimePathCreate |
200 |
|
201 |
Type (ListCoord), POINTER :: Coordinate, CurrentCoord |
202 |
Type (ListCoord), POINTER :: ScanCoord |
203 |
|
204 |
! Triggers the dynamical update of the maximum step |
205 |
LOGICAL :: DynMaxStep |
206 |
|
207 |
! Triggers the alignment of not |
208 |
LOGICAL :: Align |
209 |
|
210 |
|
211 |
|
212 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
213 |
! |
214 |
! Flags for printing |
215 |
! |
216 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
217 |
|
218 |
! Vmd is set to TRUE if user wants to use VMD to look |
219 |
! at the Path. |
220 |
! For now, used only for VASP |
221 |
|
222 |
LOGICAL :: Vmd |
223 |
|
224 |
|
225 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
226 |
! |
227 |
! Variables for periodic calculations |
228 |
! |
229 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
230 |
|
231 |
! Lattice constants |
232 |
REAL(KREAL) :: lat_a(3), lat_b(3), lat_c(3) |
233 |
! Inverse lattice constants |
234 |
REAL(KREAL) :: Latr(3,3) |
235 |
! FPBC : True if this is a periodic calculations |
236 |
LOGICAL :: FPBC |
237 |
! Possible values for ka, kb, kc in VectorPer (and other periodic operations) |
238 |
INTEGER(KINT) :: kaBeg,kaEnd,kbBeg,kbEnd,kcBeg,kcEnd |
239 |
! Number of periodic directions |
240 |
INTEGER(KINT) :: IPer |
241 |
! Reference cartesian coordinates |
242 |
REAL(KREAL), ALLOCATABLE :: XGeomRefPBC(:),YGeomRefPBC(:),ZGeomRefPBC(:) ! Nat |
243 |
! How shall we print the cartesian coordinates ? |
244 |
! if V_Direct='DIRECT' then we use fractional coord (ie divided by unit cell |
245 |
! vectors). |
246 |
CHARACTER(LCHARS) :: V_direct, V_direct_write |
247 |
|
248 |
|
249 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
250 |
! |
251 |
! Variables for VASP input/output |
252 |
! |
253 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
254 |
|
255 |
REAL(KREAL), ALLOCATABLE :: X0_vasp(:),Y0_vasp(:), Z0_vasp(:) ! nat |
256 |
! AutoCart : true if user let PATH determines which atoms should be |
257 |
! described in cartesian when COORD=MIXED |
258 |
LOGICAL :: AutoCart |
259 |
|
260 |
|
261 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
262 |
! |
263 |
! General |
264 |
! |
265 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
266 |
|
267 |
CHARACTER(2) :: Nom(0:max_Z)=(/ ' X',' H', 'HE', & |
268 |
'LI','BE', ' B',' C',' N',' O',' F','NE', & |
269 |
'NA','MG', 'AL','SI',' P',' S','CL','AR', & |
270 |
' K','CA', & |
271 |
'SC','TI',' V','CR','MN','FE','CO','NI','CU','ZN', & |
272 |
'GA','GE','AS','SE','BR','KR', & |
273 |
'RB','SR', & |
274 |
' Y','ZR','NB','MO','TC','RU','RH','PD','AG','CD', & |
275 |
'IN','SN','SB','TE',' I','XE', & |
276 |
'CS','BA', & |
277 |
'LA', & |
278 |
'CE','PR','ND','PM','SM','EU','GD','TB','DY','HO', & |
279 |
'ER','TM','YB','LU', & |
280 |
'HF','TA',' W','RE','OS','IR','PT','AU','HG', & |
281 |
'TL','PB','BI','PO','AT','RN'/) |
282 |
|
283 |
! This is the new table, more complete, taken from a periodic table |
284 |
! some value have been changed to be consistent |
285 |
REAL(KREAL) :: r_cov(0:max_Z)=(/ 1e-13, 37., 93., & |
286 |
! 2 'LI','BE', ' B',' C',' N',' O',' F','NE', |
287 |
123.,90., 82., 77., 75., 73., 71., 69., & |
288 |
! 3 'NA','MG', 'AL','SI',' P',' S','CL','AR', |
289 |
154.,136., 118.,111.,106.,102., 99., 97., & |
290 |
! 4 ' K','CA', |
291 |
203., 174., & |
292 |
! 4 'SC','TI',' V','CR','MN','FE','CO','NI','CU','ZN', |
293 |
144.,132.,122.,118.,117.,117.,116.,115.,117.,125., & |
294 |
! 4 'GA','GE','AS','SE','BR','KR', |
295 |
120.,122.,122.,117.,114.,110., & |
296 |
! 5 'RB','SR', |
297 |
216.,191., & |
298 |
! 5 ' Y','ZR','NB','MO','TC','RU','RH','PD','AG','CD', |
299 |
162.,145.,134.,130.,127.,125.,125.,128.,134.,148., & |
300 |
! 5 'IN','SN','SB','TE',' I','XE', |
301 |
144.,140.,143.,135.,133.,130., & |
302 |
! 6 'CS','BA', |
303 |
235., 198., & |
304 |
! 6 'LA', |
305 |
! 'CE','PR','ND','PM','SM','EU','GD','TB','DY','HO', & |
306 |
! 'ER','TM','YB','LU', & |
307 |
169., & |
308 |
165., 165., 164., 163., 162., 185., 161., 159., 159., 158., & |
309 |
157., 156., 184.,156., & |
310 |
! 6 'HF','TA',' W','RE','OS','IR','PT','AU','HG', |
311 |
! 6 'TL','PB','BI','PO','AT','RN'/ |
312 |
144., 134., 130., 126., 126., 127., 120., 134., 149., & |
313 |
148., 147., 146., 146., 148., 151. /) |
314 |
|
315 |
REAL(KREAL) :: Mass(0:Max_Z)=(/0.0D0,1.0078D0, 4.0026D0, & |
316 |
7.0160D0, 9.0122D0,11.0093D0, & |
317 |
12.0000D0,14.0031D0,15.9949D0,18.9984D0,19.9924D0, & |
318 |
22.9898D0,23.9850D0,26.9815D0, & |
319 |
27.9769D0,30.9738D0,31.9721D0,34.9688D0,39.9624D0, & |
320 |
39.0983D0,40.08D0, & |
321 |
44.9559D0, 47.88D0, 50.9415D0, 51.996D0, 54.9380D0, & |
322 |
55.847D0, 58.9332D0, 58.69D0, 63.546D0, 65.39D0, & |
323 |
69.72D0,72.59D0,74.9216D0,78.96D0,79.904D0,83.80D0, & |
324 |
85.4678D0,87.62D0,88.9059D0,91.224D0,92.9064D0, & |
325 |
95.94D0,98D0,101.07D0,102.906D0,106.42D0,107.868D0,112.41D0, & |
326 |
114.82D0,118.71D0,121.75D0,127.60D0,126.905D0,131.29D0, & |
327 |
! 6 'CS','BA', |
328 |
132.905D0,137.34D0, & |
329 |
! 6 'LA', |
330 |
! 'CE','PR','ND','PM','SM','EU','GD', |
331 |
! 'TB','DY','HO', 'ER','TM','YB','LU', |
332 |
138.91D0, & |
333 |
140.12D0, 130.91D0, 144.24D0,147.D0,150.35D0, 151.96D0,157.25D0, & |
334 |
158.924D0, 162.50D0, 164.93D0, 167.26D0,168.93D0,173.04D0,174.97D0, & |
335 |
! 6 'HF','TA',' W','RE','OS','IR','PT', |
336 |
! 'AU','HG', |
337 |
! 6 'TL','PB','BI','PO','AT','RN'/ |
338 |
178.49D0, 180.95D0, 183.85D0, 186.2D0, 190.2D0, 192.2D0, 195.09D0, & |
339 |
196.97D0, 200.59D0, & |
340 |
204.37D0, 207.19D0,208.98D0,210.D0,210.D0,222.D0 /) |
341 |
|
342 |
END MODULE Path_module |