Statistiques
| Révision :

root / src / Path_module.f90 @ 12

Historique | Voir | Annoter | Télécharger (14,94 ko)

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