1!
2! Copyright (C) 2004-2007 Quantum ESPRESSO group
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8MODULE ld1inc
9  USE kinds, ONLY : dp
10  USE ld1_parameters
11  USE radial_grids, ONLY: radial_grid_type, ndmx
12  USE paw_type, ONLY : paw_t
13  IMPLICIT NONE
14  SAVE
15  PRIVATE :: nwfx, nwfsx, ncmax1
16  INTEGER, PARAMETER :: lmx=3, lmx2=2*lmx
17  !
18  !    variables for the all-electron calculation
19  !
20  INTEGER  ::      &
21       nn(nwfx),   &   ! the main quantum number
22       ll(nwfx),   &   ! the orbital angular momentum
23       nwf,        &   ! the number of wavefunctions
24       isw(nwfx),  &   ! spin of the wfc. if(.not.lsd) all 1 (default)
25       nspin           ! 1 (default) or 2 (if lsd=true)
26
27  CHARACTER(len=2) ::&
28       el(nwfx)        !  the label of the states
29
30  real(DP) ::   &
31       jj(nwfx),     & ! the total angular momentum
32       oc(nwfx),     & ! the occupations of the all-electron atom
33       zed,          & ! the ionic charge
34       enne,         & ! the number of electrons
35       sl3(0:lmx2,0:lmx2,0:lmx2) ! what is this, documented somewhere?
36
37  real(DP)::          &
38       enl(nwfx),          & ! the energies of the all-electron atom
39       psi(ndmx,2,nwfx),    & ! the all-electron (dirac) wavefunctions
40                             ! psi(:,1,n) = major component for state n
41                             ! psi(:,2,n) = minor component for state n
42       rho(ndmx,2),         & ! the all-electron density
43                             ! rho(:,1) = spin-up, rho(:,2) = spin-down
44       zeta(ndmx),           & ! the all-electron magnetization
45       ! relativistic perturbative terms
46       evel(nwfx),       & ! p^4 ("velocity") correction
47       edar(nwfx),       & ! Darwin term
48       eso(nwfx)           ! spin-orbit splitting
49
50  LOGICAL :: &
51       core_state(nwfx)   ! if true the state is in the core
52  !
53  !    the parameters of the logarithmic mesh
54  !
55  TYPE(radial_grid_type) :: grid
56  !
57  !    the variables for computing logarithmic derivatives
58  !
59  INTEGER :: &
60       nld,  &  ! computes the log der of the last nld wavefunctions
61       npte     ! number of energy points
62
63  real(DP) :: &
64       rlderiv,    & ! the radius of logarithmic derivatives
65       eminld,     & ! the minimum energy
66       emaxld,     & ! the maximum energy
67       deld,       & ! the deltae of energy
68       rpwe          ! the radius of the partial wave expansion
69  !
70  !   the variables which define the pseudopotential
71  !
72  INTEGER ::       &
73       nns(nwfsx), & ! the main quantum number of pseudopotential
74       lls(nwfsx), & ! the angular momentum of pseudopotential
75       isws(nwfsx),& ! the spin of each pseudo-wavefunctions (not used)
76       ikk(nwfsx), & ! the maximum ik of each beta functions
77       ik(nwfsx),  & ! the ik that correspond to rcut
78       ikus(nwfsx), & ! the ik that corresponds to rcutus
79       nwfs,       & ! the number of pseudo wavefunctions
80       nbeta,      & ! the number of projectors
81       nsloc,      & ! the wavefunction which correspond to the loc pot
82       lloc,       & ! the l component considered as local
83       pseudotype, &  ! the type of pseudopotential
84       nstoae(nwfsx)  ! for each pseudo the all-electron
85
86  CHARACTER(len=2) :: &
87       els(nwfsx)       !  the label of the states
88
89  real(DP) ::       &
90       enls(nwfsx),      & ! the energies of the pseudo atom
91       jjs(nwfsx),       & ! the j of each wavefunction (only rel=2)
92       ocs(nwfsx),       & ! the occupations of the pseudo atom
93       rcut(nwfsx),      & ! the cut-off radius for pseudowavefunctions
94       rcutus(nwfsx),    & ! the cut-off radius for us-pseudowavefunctions
95       rcloc,            & ! cut-off for local potential
96       ecutrho,          & ! suggested cut-off for the charge
97       ecutwfc,          & ! suggested cut-off for the wavefunctions
98       zval,             & ! the ionic pseudo charge
99       phis(ndmx,nwfsx),  & ! the pseudo wavefunctions
100       psipsus(ndmx,nwfx),& ! the all-electron wavefunctions for us pseudo
101       rhos(ndmx,2),      & ! the pseudo density
102       zetas(ndmx),       & ! the pseudo magnetization
103       vnl(ndmx,0:3,2),   & ! the pseudopotential in semilocal form
104       betas(ndmx,nwfsx), & ! the projector functions
105       chis(ndmx,nwfsx),  & ! auxiliary functions
106       rho0,             & ! value of the charge at the origin
107       bmat(nwfsx,nwfsx), &! the pseudo coefficients (unscreened D)
108       ddd(nwfsx,nwfsx,2),&! the screened D
109       qq(nwfsx,nwfsx),   &! the integrals of the qvan
110       qvan(ndmx,nwfsx,nwfsx), & ! the augmentation functions
111       qvanl(ndmx,nwfsx,nwfsx,0:lmx2) ! the augmentation functions, l dependent
112
113  LOGICAL :: &
114       tm,            &!  if true use Troullier-Martins for norm-conserving PP
115       new(nwfsx)      !  if true the fit is on arbitrary energy
116  !
117  !    the variable for multiconfigurations
118  !
119  INTEGER ::                 &
120       nconf,                & ! number of configuration
121       nstoaec(nwfsx,ncmax1),& ! correspondence all-electron test
122       lsdts(ncmax1),        & ! for each configuration the lsd
123       nwftsc(ncmax1),       & ! number of wavefunctions for each config.
124       nntsc(nwfsx,ncmax1),lltsc(nwfsx,ncmax1),& ! the quantum numbers of
125                                ! each configuration
126       iswtsc(nwfsx,ncmax1)    ! the spin index
127
128  CHARACTER(len=2) ::  &
129       eltsc(nwfsx,ncmax1)     !  the labels for each configuration
130
131  real(DP) ::              &
132       rcuttsc(nwfsx,ncmax1),   & ! the cut-off radius of each configuration
133       rcutustsc(nwfsx,ncmax1), & ! cut-off radius for us
134       jjtsc(nwfsx,ncmax1),     & ! the j of a configuration
135       octsc(nwfsx,ncmax1),     & ! the occupations of each configuration
136       enltsc(nwfsx,ncmax1)       ! the energies of each configuration
137  !
138  ! for tests
139  !
140  INTEGER ::        &
141       nnts(nwfsx),  &   ! the main quantum number of pseudopotential
142       llts(nwfsx),  &   ! the angular momentum of pseudopotential
143       iswts(nwfsx), &   ! spin of the wfc. if(.not.lsd) all 1 (default)
144       nstoaets(nwfsx), & ! for each test wavefunction the all-electron
145       nwfts             ! the number of pseudo wavefunctions
146
147  real(DP) ::        &
148       enlts(nwfsx),       & ! the energies for the test configuration
149       phits(ndmx,nwfsx),   & ! the pseudo wavefunctions
150       rcutts(nwfsx),      & ! cut-off radius for test wavefunction
151       rcutusts(nwfsx),    & ! us cut-off radii for test wavefunct.
152       jjts(nwfsx),        & ! jj of the test function (rel=2)
153       octs(nwfsx)           ! the occupation numbers
154
155  CHARACTER(len=2) ::  &
156       elts(nwfsx)           ! the label of the states
157  !
158  ! for LDA-1/2
159  !
160  real(DP) :: rcutv ! CUT for LDA-1/2
161  !
162  !    The control of the run
163  !
164  INTEGER ::      &
165       iter,      &  ! iteration conter
166       lsd,       &  ! if true lsd calculation
167       isic,      &  ! if true uses self-interaction correction
168       latt,      &  ! if true Latter's correction is applied
169       iswitch,   &  ! control the type of run
170       max_out_wfc, & ! maximum number of wavefunctions written on the
171                     !   wavefunctions file.
172       rel           ! 0 nonrelativistic calculation
173                     ! 1 scalar relativistic calculation
174                     ! 2 calculation with the full dirac equation
175  LOGICAL ::      &
176       lsmall,    &     ! if true writes the small component on file
177       relpert,   &     ! compute relativistic perturbative corrections
178       frozen_core, &   ! if true the all-electron calculation is frozen core
179       write_coulomb, & ! if true write a fake UPF pseudopotential file named
180                        ! X.coul (X=atomic symbol) - for usage in special cases
181                        ! when the bare coulomb potential is required
182       noscf            ! if true a hydrogenic atom is solved. The charge
183                        ! density is not computed.
184
185
186
187  CHARACTER(len=4) :: &
188       verbosity     ! if 'high' writes more information on output
189
190
191  real(DP) :: &
192       beta,       &   ! the mixing parameter
193       tr2,        &   ! the required precision of the scf
194       eps0            ! the reached precision of the scf
195  !
196  !    parameters for the old type pseudopotential
197  !
198  INTEGER ::   &
199       lmin,   &  ! the minimum angular momentum
200       lmax,   &  ! the maximum angular momentum
201       nlc,    &  ! number of core functions
202       nnl        ! number of angular momentum functions
203
204  real(DP) ::     &
205       cc(2),          & ! the coeffients of the core part
206       alpc(2),        & ! the alpha parameters of the core
207       alc(6,0:3),     & ! the coefficients of the pseudopotential
208       alps(3,0:3)       ! the alpha parameters
209  !
210  !   the energy parameters
211  !
212  real(DP) :: &
213       etot,       &    ! total energy
214       etot0,      &    ! saved value of the total energy
215       ekin,       &    ! kinetic energy
216       encl,       &    ! nuclear Coulomb energy
217       ehrt,       &    ! Hartree energy
218       ecxc,       &    ! exchange-correlation energy
219       ecc,        &    ! core-only contribution to the energy
220       evxt,       &    ! external field energy
221       epseu,      &    ! pseudopotential energy
222       ekinc,      &    ! core kinetic energy
223       ekinc0,     &    ! core kinetic energy
224       ekinv,      &    ! valence kinetic energy
225       enclv, enclc,  & ! nuclear Coulomb energy of valence and core
226       ehrtvv,     &    ! valence-valence Hartree energy
227       ehrtcv,     &    ! core-valence Hartree energy
228       ehrtcc,     &    ! core-core Hartree energy
229       ae_fc_energy, &  ! frozen core energy calculated with all-electron char
230       dhrsic,     &    ! Hartree sic energy
231       dxcsic,     &    ! exchange sic energy
232       etots,      &    ! total pseudopotential energy
233       etots0           ! saved value of the total pseudopotential energy
234  !
235  !  variable for nlcc
236  !
237  real(DP) :: &
238       rcore,      &  ! the points where core charge is smooth
239       rhoc(ndmx)      ! the core charge
240
241  LOGICAL :: &
242       new_core_ps, & ! if true pseudize the core charge with bessel functions
243       nlcc    ! if true nlcc pseudopotential
244  !
245  !  the potential for the scf
246  !
247  real(DP) ::   &
248       v0(ndmx),      & ! the coulomb potential
249       vpot(ndmx,2),  & ! the all-electron scf potential
250       vxt(ndmx),     & ! the external potential
251       vh(ndmx),      & ! the hartree potential
252       vxc(ndmx,2),   & ! the exchange and correlation potential
253       exc(ndmx),     & ! the exchange and correlation energy
254       excgga(ndmx),  & ! the GGA exchange and correlation energy
255       vxcts(ndmx,2), & ! the pseudo exchange and correlation potential
256       excts(ndmx),   & ! the pseudo exchange and correlation energy
257       excggats(ndmx),& ! the GGA exchange and correlation energy
258       vpstot(ndmx,2),& ! the total local pseudopotential
259       vpsloc(ndmx)  ,& ! the local pseudopotential
260       vx(ndmx,2)    ,& ! the OEP-X potential (when needed)
261       enzero(2)
262  real(DP) ::  &
263       tau(ndmx,2),   & ! kinetic energy density for metaGGA
264       vtau(ndmx)       ! potential for metaGGA
265  real(DP), ALLOCATABLE ::  &
266       vsic(:,:), vsicnew(:), vhn1(:), egc(:) ! potentials for SIC
267  !
268  LOGICAL :: lsave_wfc  ! if true, wfcs (AE and PS) are saved to the UFP file
269  !
270  !  variables needed for PAW dataset generation and test
271  !
272  LOGICAL :: &
273       lpaw,      &! if true generate or test a PAW dataset
274       lnc2paw, &  ! if true the PAW dataset is generate from the NC one
275       rmatch_augfun_nc, &  ! if .true. the norm conserving radii are
276                            ! used to pseudize the q functions
277       use_paw_as_gipaw ! if true, PAW data will be used for GIPAW
278  TYPE(paw_t) :: &
279       pawsetup    ! the PAW dataset
280  real(DP) ::       &
281       rmatch_augfun,     & ! define the matching radius for paw aug.fun.
282       psipaw(ndmx,nwfsx),& ! the all-electron wavefunctions for any beta
283       psipaw_rel(ndmx,nwfsx),& ! the all-electron wfc small component
284       aeccharge(ndmx),   & ! true, not smoothened, AE core charge for PAW
285       psccharge(ndmx),   & ! smoothened core charge for PAW
286       paw_energy(5,3)
287
288   CHARACTER(len=20) ::&
289       which_augfun     ! choose shape of paw fun. (GAUSS, BESSEL..)
290  !
291  ! conversion factor
292  !
293  real(DP) :: &
294             rytoev_fact    ! Conversion from Ry and eV. A value
295                            ! different from default can be used
296                            ! to reproduce results of old papers.
297  real(DP) :: &
298             cau_fact       ! speed of light in atomic units.
299  !
300  !  Auxiliary quantities for verbose output
301  !
302  real(DP) ::       &
303       aevcharge(ndmx,2)     ! the all-electron valence charge
304
305  !
306  !  file names
307  !
308  CHARACTER(len=75)  :: title  ! the title of the run
309  CHARACTER(len=75)  :: author ! the author of the pseudopotential
310  CHARACTER(len=240) :: prefix ! prefix for file names
311  CHARACTER(len=256) ::      & !
312       file_pseudo,          & ! input file containing the pseudopotential
313       file_pseudopw           ! output file where the pseudopot is written
314  LOGICAL            ::      &
315       use_xsd = .FALSE.       ! if .true. follow xsd schema else use upf-v2.1 format
316  CHARACTER(len=256) ::      & ! output filenames read from input, containing:
317       file_charge,          & ! all-electron total charge only
318       file_chi,             & ! chi functions
319       file_beta,            & ! beta functions
320       file_qvan,            & ! qvan functions
321       file_screen,          & ! screening potential
322       file_core,            & ! core charge
323       file_recon              ! information for paw reconstruction
324  ! the following filenames are determined by "prefix", not read from input
325  CHARACTER(len=256) ::      & ! output files, containing:
326       file_wfcaegen,        & ! all-electron wavefunctions for generation
327       file_wfcncgen,        & ! norm-conserving wavefunctions for generation
328       file_wfcusgen,        & ! ultra-soft wavefunctions for generation
329       file_potscf,          & ! scf potential at each iteration
330       file_wavefunctions,   & ! all-electron results for orbitals
331       file_wavefunctionsps, & ! pseudopotential results for orbitals
332       file_logder,          & ! all-electron logarithmic derivatives
333       file_logderps,        & ! pseudopotential logarithmic derivatives
334       file_pawexp,          & ! quality index of partial wave expansion
335       file_tests              ! results of pseudopotential tests
336  !
337  ! vdw calculation
338  !
339  LOGICAL :: vdw        ! optional variable
340  !
341  real(DP) :: um,     & ! maximum frequency
342              du,     & ! step of frequency
343              tr_s    ! threshold for scf solution of modified Sternheimer equation
344  !
345  ! test on ghosts and convergences with spherical Bessel functions
346  !
347  real(DP) :: ecutmin, & ! min kinetic energy cutoff for j_l(qr)
348              ecutmax, & ! max energy cutoff
349              decut,   & ! step: ecut = ecutmin, ecutmin+decut, ... , ecutmax
350              rm         ! radius of the box
351  !
352  ! (GI)PAW reconstruction
353  !
354  LOGICAL :: lgipaw_reconstruction
355  REAL ( dp ) :: wfc_ae_recon(ndmx,nwfx)
356  REAL ( dp ) :: wfc_ps_recon(ndmx,nwfsx)
357  REAL ( dp ) :: wfc_us_recon(ndmx,nwfsx)
358  !
359END MODULE ld1inc
360