root / src / Path_module.f90 @ 2
Historique | Voir | Annoter | Télécharger (11,13 ko)
1 |
MODULE Path_module |
---|---|
2 |
! This module contains most of the variables needed for the path |
3 |
|
4 |
use VarTypes |
5 |
|
6 |
IMPLICIT NONE |
7 |
|
8 |
SAVE |
9 |
|
10 |
INTEGER(KINT), PARAMETER :: NMaxL=21 |
11 |
INTEGER(KINT), PARAMETER :: Max_Z=86 |
12 |
INTEGER(KINT), PARAMETER :: MaxFroz=100 |
13 |
REAL(KREAL), PARAMETER :: a0=0.529177249d0 |
14 |
REAL(KREAL), PARAMETER :: Unit=1.d0/a0 |
15 |
REAL(KREAL), PARAMETER :: au2kcal=627.509608d0 |
16 |
REAL(KREAL) :: Pi |
17 |
|
18 |
! Frozen contains the indices of frozen atoms |
19 |
INTEGER(KINT),ALLOCATABLE :: Frozen(:) !Nat |
20 |
! Cart contains the indices of atoms described in cartesian coords |
21 |
INTEGER(KINT),ALLOCATABLE :: Cart(:) !Nat |
22 |
! intFroz is the number of internal coord frozen |
23 |
! NFroz the number of frozen atoms |
24 |
! Ncart the number of atoms described in cartesian coords |
25 |
INTEGER(KINT) :: IntFroz, NFroz, NCart |
26 |
! FrozAtoms is true for a frozen atom, false else. |
27 |
LOGICAL, ALLOCATABLE :: FrozAtoms(:) !! Nat |
28 |
! Number of Primitives (mainly for Baker coordinates) |
29 |
INTEGER(KINT) :: NPrim |
30 |
! Nat number of atoms |
31 |
INTEGER(KINT) :: Nat |
32 |
! NGeomI number of initial geometries |
33 |
! NgeomF number of final geometries |
34 |
INTEGER(KINT) :: NGeomI, NGeomF |
35 |
! NCoord=3*Nat or NFree depending on the coordinate choice |
36 |
INTEGER(KINT) :: NCoord |
37 |
INTEGER(KINT) :: NMaxPtPath=1000 |
38 |
! IReparam is the period of reparameterization of the Path |
39 |
INTEGER(KINT) :: IReparam=1 |
40 |
! IReparamT is the period of reparameterization of the tangents along the path |
41 |
! Be default IReparamT=IReparam |
42 |
INTEGER(KINT) :: IReparamT |
43 |
! ISpline is the iteration number where spline interpolation starts to be used |
44 |
! instead of linear interpolation |
45 |
INTEGER(KINT) :: ISpline=1 |
46 |
! Linear: if TRUE, then we perform linear interpolation and not spline |
47 |
LOGICAL :: Linear |
48 |
|
49 |
! FrozTol is the criterion to decide wether a frozen atom has moved between |
50 |
! two initial geometries |
51 |
REAL(KREAL) :: FrozTol=1e-4 |
52 |
|
53 |
! BoxTol is the criterion to decide wether an atom has crossed the box between |
54 |
! two initial geometries |
55 |
REAL(KREAL) :: BoxTol=0.5 |
56 |
|
57 |
|
58 |
LOGICAL :: Freq, MW, Bohr, Renum, Hinv |
59 |
LOGICAL :: OptReac, OptProd, PathOnly |
60 |
LOGICAL :: IniHup,HupNeighbour |
61 |
|
62 |
REAL(KREAL) :: Fact,FTan |
63 |
! IGeomRef is the index of the reference geometry, used to calculate the Zmat |
64 |
! or the Baker coordinates. |
65 |
INTEGER(KINT) :: IGeomRef=-1 |
66 |
! For geometry optimization , OptGeom is the index of the starting geometry |
67 |
INTEGER(KINT) :: OptGeom=-1 |
68 |
|
69 |
! Optimization parameter |
70 |
INTEGER(KINT) :: MaxCyc |
71 |
REAL(KREAL) :: SThresh, Smax, SthreshRms |
72 |
REAL(KREAL) :: GThresh, GThreshRMS |
73 |
|
74 |
! Number of steps in memory for Step_RFO_all |
75 |
INTEGER(KINT) :: NGintMax = 10 |
76 |
|
77 |
CHARACTER(SCHARS) :: Coord='HYBRID' |
78 |
CHARACTER(SCHARS) :: Step_method='RFO' |
79 |
CHARACTER(SCHARS) :: Prog="GAUSSIAN" |
80 |
CHARACTER(VLCHARS) :: ProgExe="g03" |
81 |
|
82 |
CHARACTER(SCHARS) :: runtyp='GEOMETRY OPTIMIZATION' |
83 |
CHARACTER(SCHARS) :: hesupd="BFGS" |
84 |
|
85 |
REAL(KREAL), ALLOCATABLE, TARGET :: XyzGeomI(:,:,:) ! (NGeomI,3,Nat) |
86 |
REAL(KREAL), ALLOCATABLE :: XyzGeomF(:,:,:) ! (NGeomF,3,Nat) |
87 |
REAL(KREAL), ALLOCATABLE :: XyzTangent(:,:) ! (NGeomF,3*Nat) |
88 |
REAL(KREAL), ALLOCATABLE :: IntTangent(:,:) ! (NGeomF,Nfree=3Nat-6) |
89 |
REAL(KREAL), ALLOCATABLE :: IntCoordI(:,:) ! (NGeomI,3*Nat-6) |
90 |
! IntCoordF: Final Internal coordinates for number of final geometries. |
91 |
! 3*Nat-6 is the number of coordinates (NCoord) of each geometry. |
92 |
REAL(KREAL), ALLOCATABLE :: IntCoordF(:,:) ! (NGeomF,3*Nat-6) |
93 |
REAL(KREAL), ALLOCATABLE :: Vfree(:,:) ! (Ncoord,Ncoord) |
94 |
REAL(KREAL), ALLOCATABLE :: SGeom(:) ! (NGeomF) |
95 |
REAL(KREAL), ALLOCATABLE :: Energies(:) ! NGeomF |
96 |
! NCoord=3*Nat or NFree depending on the coordinate choice |
97 |
REAL(KREAL), ALLOCATABLE :: Grad(:,:) ! (NGeomF,NCoord) |
98 |
REAL(KREAL), ALLOCATABLE :: Hess(:,:,:) !(NgeomF, N,N) |
99 |
REAL(KREAL), ALLOCATABLE :: DzDc(:,:,:,:) ! (3,Nat,3,Nat) |
100 |
REAL(KREAL), ALLOCATABLE :: BMat_BakerT(:,:) ! (3*Nat,NCoord) |
101 |
INTEGER(KINT), ALLOCATABLE :: IndZmat(:,:) ! (Nat,5) |
102 |
INTEGER(KINT), ALLOCATABLE :: Order(:),OrderInv(:) ! Nat |
103 |
CHARACTER(10), ALLOCATABLE :: AtName(:) ! Nat |
104 |
INTEGER(KINT), ALLOCATABLE :: Atome(:) ! Nat |
105 |
REAL(KREAL), ALLOCATABLE :: MassAt(:) ! Nat |
106 |
REAL(KREAL), ALLOCATABLE :: BTransInv(:,:) ! BTransInv (3*Nat-6,3*Nat), used for Baker case. |
107 |
REAL(KREAL), ALLOCATABLE :: BTransInvF(:,:,:) ! BTransInvF (NGeomF,3*Nat-6,3*Nat) |
108 |
! BTransInv_local (3*Nat-6,3*Nat), used for Baker case in Opt_Geom.f90 |
109 |
REAL(KREAL), ALLOCATABLE :: BTransInv_local(:,:) |
110 |
REAL(KREAL), ALLOCATABLE :: UMat(:,:) !(NPrim,3*Nat-6) |
111 |
REAL(KREAL), ALLOCATABLE :: UMat_local(:,:) !(NPrim,3*Nat-6) |
112 |
REAL(KREAL), ALLOCATABLE :: UMatF(:,:,:) !(NGeomF,NPrim,3*Nat-6) |
113 |
!REAL(KREAL), ALLOCATABLE :: IntCoordIBaker(:,:) ! (NGeomI,NCoord=3*Nat-6) |
114 |
! IntCoordIBaker allocated in PathCreate.f90 |
115 |
REAL(KREAL), ALLOCATABLE :: Xprimitive(:,:) ! Xprimitive(NgeomI,NPrim) |
116 |
REAL(KREAL), ALLOCATABLE :: Xprimitive_t(:) ! used in ConvertBakerInternal_cart.f as a temporary variable. |
117 |
REAL(KREAL), ALLOCATABLE :: XprimitiveF(:,:) ! Xprimitive(NgeomF,NPrim) |
118 |
REAL(KREAL), ALLOCATABLE :: GeomOld_all(:,:) |
119 |
REAL(KREAL), ALLOCATABLE :: GeomOld(:) ! Used in DIIS step method. |
120 |
|
121 |
LOGICAL, PARAMETER :: FRot=.TRUE., FAlign=.TRUE. |
122 |
REAL(KREAL), ALLOCATABLE :: BprimT(:,:) !(3*Nat,NPrim). This is B^prim. |
123 |
REAL(KREAL), ALLOCATABLE :: BBT(:,:) ! BBT (3*Nat-6,3*Nat-6), used for Baker case |
124 |
REAL(KREAL), ALLOCATABLE :: BBT_inv(:,:) ! BBT_inv (3*Nat-6,3*Nat-6), used for Baker case |
125 |
INTEGER(KINT) :: Symmetry_elimination |
126 |
LOGICAL :: FirstTimePathCreate |
127 |
|
128 |
Type (ListCoord), POINTER :: Coordinate, CurrentCoord |
129 |
Type (ListCoord), POINTER :: ScanCoord |
130 |
|
131 |
! Triggers the dynamical update of the maximum step |
132 |
LOGICAL :: DynMaxStep |
133 |
|
134 |
! Triggers the alignment of not |
135 |
LOGICAL :: Align |
136 |
|
137 |
|
138 |
|
139 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
140 |
! |
141 |
! Flags for printing |
142 |
! |
143 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
144 |
|
145 |
! Vmd is set to TRUE if user wants to use VMD to look |
146 |
! at the Path. |
147 |
! For now, used only for VASP |
148 |
|
149 |
LOGICAL :: Vmd |
150 |
|
151 |
|
152 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
153 |
! |
154 |
! Variables for VASP input/output |
155 |
! |
156 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
157 |
|
158 |
REAL(KREAL) :: lat_a(3), lat_b(3), lat_c(3) |
159 |
REAL(KREAL), ALLOCATABLE :: X0_vasp(:),Y0_vasp(:), Z0_vasp(:) ! nat |
160 |
REAL(KREAL) :: Latr(3,3) |
161 |
CHARACTER(LCHARS) :: V_direct |
162 |
! AutoCart : true if user let PATH determines which atoms should be |
163 |
! described in cartesian when COORD=MIXED |
164 |
LOGICAL :: AutoCart |
165 |
|
166 |
|
167 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
168 |
! |
169 |
! General |
170 |
! |
171 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
172 |
|
173 |
CHARACTER(2) :: Nom(0:max_Z)=(/ ' X',' H', 'HE', & |
174 |
'LI','BE', ' B',' C',' N',' O',' F','NE', & |
175 |
'NA','MG', 'AL','SI',' P',' S','CL','AR', & |
176 |
' K','CA', & |
177 |
'SC','TI',' V','CR','MN','FE','CO','NI','CU','ZN', & |
178 |
'GA','GE','AS','SE','BR','KR', & |
179 |
'RB','SR', & |
180 |
' Y','ZR','NB','MO','TC','RU','RH','PD','AG','CD', & |
181 |
'IN','SN','SB','TE',' I','XE', & |
182 |
'CS','BA', & |
183 |
'LA', & |
184 |
'CE','PR','ND','PM','SM','EU','GD','TB','DY','HO', & |
185 |
'ER','TM','YB','LU', & |
186 |
'HF','TA',' W','RE','OS','IR','PT','AU','HG', & |
187 |
'TL','PB','BI','PO','AT','RN'/) |
188 |
|
189 |
! This is the new table, more complete, taken from a periodic table |
190 |
! some value have been changed to be consistent |
191 |
REAL(KREAL) :: r_cov(0:max_Z)=(/ 1e-13, 37., 93., & |
192 |
! 2 'LI','BE', ' B',' C',' N',' O',' F','NE', |
193 |
123.,90., 82., 77., 75., 73., 71., 69., & |
194 |
! 3 'NA','MG', 'AL','SI',' P',' S','CL','AR', |
195 |
154.,136., 118.,111.,106.,102., 99., 97., & |
196 |
! 4 ' K','CA', |
197 |
203., 174., & |
198 |
! 4 'SC','TI',' V','CR','MN','FE','CO','NI','CU','ZN', |
199 |
144.,132.,122.,118.,117.,117.,116.,115.,117.,125., & |
200 |
! 4 'GA','GE','AS','SE','BR','KR', |
201 |
120.,122.,122.,117.,114.,110., & |
202 |
! 5 'RB','SR', |
203 |
216.,191., & |
204 |
! 5 ' Y','ZR','NB','MO','TC','RU','RH','PD','AG','CD', |
205 |
162.,145.,134.,130.,127.,125.,125.,128.,134.,148., & |
206 |
! 5 'IN','SN','SB','TE',' I','XE', |
207 |
144.,140.,143.,135.,133.,130., & |
208 |
! 6 'CS','BA', |
209 |
235., 198., & |
210 |
! 6 'LA', |
211 |
! 'CE','PR','ND','PM','SM','EU','GD','TB','DY','HO', & |
212 |
! 'ER','TM','YB','LU', & |
213 |
169., & |
214 |
165., 165., 164., 163., 162., 185., 161., 159., 159., 158., & |
215 |
157., 156., 184.,156., & |
216 |
! 6 'HF','TA',' W','RE','OS','IR','PT','AU','HG', |
217 |
! 6 'TL','PB','BI','PO','AT','RN'/ |
218 |
144., 134., 130., 126., 126., 127., 120., 134., 149., & |
219 |
148., 147., 146., 146., 148., 151. /) |
220 |
|
221 |
REAL(KREAL) :: Mass(0:Max_Z)=(/0.0D0,1.0078D0, 4.0026D0, & |
222 |
7.0160D0, 9.0122D0,11.0093D0, & |
223 |
12.0000D0,14.0031D0,15.9949D0,18.9984D0,19.9924D0, & |
224 |
22.9898D0,23.9850D0,26.9815D0, & |
225 |
27.9769D0,30.9738D0,31.9721D0,34.9688D0,39.9624D0, & |
226 |
39.0983D0,40.08D0, & |
227 |
44.9559D0, 47.88D0, 50.9415D0, 51.996D0, 54.9380D0, & |
228 |
55.847D0, 58.9332D0, 58.69D0, 63.546D0, 65.39D0, & |
229 |
69.72D0,72.59D0,74.9216D0,78.96D0,79.904D0,83.80D0, & |
230 |
85.4678D0,87.62D0,88.9059D0,91.224D0,92.9064D0, & |
231 |
95.94D0,98D0,101.07D0,102.906D0,106.42D0,107.868D0,112.41D0, & |
232 |
114.82D0,118.71D0,121.75D0,127.60D0,126.905D0,131.29D0, & |
233 |
! 6 'CS','BA', |
234 |
132.905D0,137.34D0, & |
235 |
! 6 'LA', |
236 |
! 'CE','PR','ND','PM','SM','EU','GD', |
237 |
! 'TB','DY','HO', 'ER','TM','YB','LU', |
238 |
138.91D0, & |
239 |
140.12D0, 130.91D0, 144.24D0,147.D0,150.35D0, 151.96D0,157.25D0, & |
240 |
158.924D0, 162.50D0, 164.93D0, 167.26D0,168.93D0,173.04D0,174.97D0, & |
241 |
! 6 'HF','TA',' W','RE','OS','IR','PT', |
242 |
! 'AU','HG', |
243 |
! 6 'TL','PB','BI','PO','AT','RN'/ |
244 |
178.49D0, 180.95D0, 183.85D0, 186.2D0, 190.2D0, 192.2D0, 195.09D0, & |
245 |
196.97D0, 200.59D0, & |
246 |
204.37D0, 207.19D0,208.98D0,210.D0,210.D0,222.D0 /) |
247 |
|
248 |
END MODULE Path_module |