! ! Copyright (C) 2002-2007 Quantum-Espresso group ! This file is distributed under the terms of the ! GNU General Public License. See the file `License' ! in the root directory of the present distribution, ! or http://www.gnu.org/copyleft/gpl.txt . ! MODULE pseudo_types ! this module contains the definitions of several TYPE structures, ! together with their allocation/deallocation routines USE kinds, ONLY: DP use radial_grids, ONLY: radial_grid_type IMPLICIT NONE SAVE ! TYPE :: paw_t ! ! Type describing a PAW dataset (temporary). ! Functions are defined on a logarithmic radial mesh. ! CHARACTER(LEN=2) :: symbol REAL (DP) :: zval REAL (DP) :: z CHARACTER(LEN=80):: dft TYPE(radial_grid_type) :: grid REAL (DP) :: rmatch_augfun ! the matching radius for augmentation charges LOGICAL :: nlcc ! nonlinear core correction INTEGER :: nwfc ! number of wavefunctions/projectors INTEGER :: lmax ! maximum angular momentum of projectors INTEGER, POINTER :: l(:) !l(nwfsx) ! angular momentum of projectors INTEGER, POINTER :: ikk(:) !ikk(nwfsx) ! cutoff radius for the projectors INTEGER :: irc ! r(irc) = radius of the augmentation sphere CHARACTER(LEN=2),POINTER :: els (:) ! the name of the wavefunction REAL (DP), POINTER :: & oc(:), & !(nwfsx) the occupations enl(:), & !(nwfsx) the energy of the wavefunctions jj (:), & ! the total angular momentum rcutus (:), & ! the cutoff aewfc(:,:), & !(ndmx,nwfsx) all-electron wavefunctions pswfc(:,:), & !(ndmx,nwfsx) pseudo wavefunctions proj(:,:), & !(ndmx,nwfsx) projectors augfun(:,:,:,:), &!(ndmx,nwfsx,nwfsx,0:2*lmaxx+1), augmom(:,:,:), & !(nwfsx,nwfsx,0:2*lmaxx) moments of the augmentation functions aeccharge(:), & !(ndmx) AE core charge * 4PI r^2 psccharge(:), & !(ndmx) PS core charge * 4PI r^2 pscharge(:), & !(ndmx) PS charge * 4PI r^2 aeloc(:), & !(ndmx) descreened AE potential: v_AE-v_H[n1]-v_XC[n1+nc] psloc(:), & !(ndmx) descreened local PS potential: v_PS-v_H[n~+n^]-v_XC[n~+n^+n~c] kdiff(:,:), & !(nwfsx,nwfsx) kinetic energy differences dion(:,:) !(nwfsx,nwfsx) descreened D coeffs !!! Notes about screening: !!! Without nlcc, the local PSpotential is descreened with n~+n^ only. !!! The local AEpotential is descreened ALWAYS with n1+nc. This improves !!! the accuracy, and will not cost in the plane wave code (atomic !!! contribution only). END TYPE paw_t ! ! Additional data to make a PAW setup out of an US pseudo, ! they are all stored on a radial grid: TYPE paw_in_upf REAL(DP),POINTER :: aug(:,:,:,:) ! Augmentation charge REAL(DP),POINTER :: ae_rho_atc(:) ! AE core charge (pseudo ccharge ! is already included in upf) REAL(DP),POINTER :: pfunc(:,:,:),&! Psi_i(r)*Psi_j(r) ptfunc(:,:,:) ! as above, but for pseudo REAL(DP),POINTER :: ae_vloc(:) ! AE local potential (pseudo vloc ! is already included in upf) REAL(DP),POINTER :: kdiff(:,:) ! kinetic energy difference AE-pseudo REAL(DP),POINTER :: oc(:) ! starting occupation used to init becsum ! they differ from US ones because they ! are indexed on BETA functions, non on WFC REAL(DP),POINTER :: augmom(:,:,:) ! multipole AE-pseudo (i,j,l=0:2*lmax) REAL(DP) :: raug ! augfunction max radius INTEGER :: iraug ! index on rgrid closer to, and >, raug INTEGER :: irmax ! max{ iraug , kkbeta } == max radius to integrate INTEGER :: lmax_aug ! max angmom of augmentation functions, it is == ! to 2* max{l of pseudized wavefunctions} ! note that nqlc of upf also include the angmom of ! empty virtual channel used to generate local potential INTEGER :: lmax_phi ! INTEGER :: lmax_rho ! CHARACTER(len=12):: augshape ! shape of augmentation charge END TYPE paw_in_upf TYPE pseudo_upf CHARACTER(LEN=80):: generated ! CHARACTER(LEN=80):: date_author ! Misc info CHARACTER(LEN=80):: comment ! CHARACTER(LEN=2) :: psd ! Element label CHARACTER(LEN=20) :: typ ! Pseudo type ( NC or US ) LOGICAL :: tvanp ! .true. if Ultrasoft LOGICAL :: nlcc ! Non linear core corrections CHARACTER(LEN=20) :: dft ! Exch-Corr type REAL(DP) :: zp ! z valence REAL(DP) :: etotps ! total energy REAL(DP) :: ecutwfc ! suggested cut-off for wfc REAL(DP) :: ecutrho ! suggested cut-off for rho LOGICAL :: has_so ! if .true. includes spin-orbit REAL(DP) :: xmin ! the minimum x of the linear mesh REAL(DP) :: rmax ! the maximum radius of the mesh REAL(DP) :: zmesh ! the nuclear charge used for mesh REAL(DP) :: dx ! the deltax of the linear mesh INTEGER, POINTER :: nn(:) ! nn(nwfc) quantum number of wfc REAL(DP), POINTER :: rcut(:) ! cut-off radius(nbeta) REAL(DP), POINTER :: rcutus(:)! ultrasoft cut-off radius (nbeta) REAL(DP), POINTER :: epseu(:) ! energy (nwfc) REAL(DP), POINTER :: jchi(:) ! jchi(nwfc) j=l+1/2 or l-1/2 of wfc REAL(DP), POINTER :: jjj(:) ! jjj(nbeta) j=l+1/2 or l-1/2 of beta INTEGER :: nv ! UPF file version number INTEGER :: lmax ! maximum l component in beta INTEGER :: mesh ! number of points in the radial mesh INTEGER :: nwfc ! number of atomic wavefunctions INTEGER :: nbeta ! number of projectors INTEGER :: kkbeta ! kkbeta=max(kbeta(:)) ! kbeta<=mesh is the number of grid points for each beta function ! beta(r,nb) = 0 for r > r(kbeta(nb)) ! kkbeta<=mesh is the largest of such number so that for all beta ! beta(r,nb) = 0 for r > r(kkbeta) CHARACTER(LEN=2), POINTER :: els(:) ! els(nwfc) label of wfc CHARACTER(LEN=2), POINTER :: els_beta(:) ! els(nbeta) label of beta INTEGER, POINTER :: lchi(:) ! lchi(nwfc) value of l for wavefcts REAL(DP), POINTER :: oc(:) ! oc(nwfc) occupancies for wavefcts REAL(DP), POINTER :: r(:) ! r(mesh) radial grid REAL(DP), POINTER :: rab(:) ! rab(mesh) dr(x)/dx (x=linear grid) REAL(DP), POINTER :: rho_atc(:) ! rho_atc(mesh) atomic core charge REAL(DP), POINTER :: vloc(:) ! vloc(mesh) local atomic potential INTEGER, POINTER :: lll(:) ! lll(nbeta) l of each projector INTEGER, POINTER :: kbeta(:) ! kbeta(nbeta) see above kkbeta REAL(DP), POINTER :: beta(:,:) ! beta(mesh,nbeta) projectors REAL(DP), POINTER :: aewfc(:,:) ! wfc(mesh,nbeta) all-electron wfc REAL(DP), POINTER :: pswfc(:,:) ! wfc(mesh,nbeta) pseudo wfc INTEGER :: nd REAL(DP), POINTER :: dion(:,:) ! dion(nbeta,nbeta) atomic D_{mu,nu} INTEGER :: nqf ! number of Q coefficients INTEGER :: nqlc ! number of angular momenta in Q REAL(DP), POINTER :: rinner(:) ! rinner(0:2*lmax) r_L REAL(DP), POINTER :: qqq(:,:) ! qqq(nbeta,nbeta) q_{mu,nu} REAL(DP), POINTER :: qfunc(:,:) ! qfunc(mesh,nbeta*(nbeta+1)/2) ! Q_{mu,nu}(|r|) function for |r|> r_L REAL(DP), POINTER :: qfuncl(:,:,:)! qfuncl(mesh,nbeta*(nbeta+1)/2,l) ! Q_{mu,nu}(|r|) function for |r|> REAL(DP), POINTER :: qfcoef(:,:,:,:) ! qfcoef(nqf,0:2*lmax,nbeta,nbeta) ! coefficients for Q for |r|