quantum-espresso/Modules/wannier.f90

53 lines
2.9 KiB
Fortran

!
! Copyright (C) 2003-2010 Quantum ESPRESSO and Wannier90 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 wannier
USE kinds, only : DP
!integer, allocatable :: nnb(:) ! #b (ik)
integer :: nnb ! #b
integer, allocatable :: kpb(:,:) ! k+b (ik,ib)
integer, allocatable :: g_kpb(:,:,:) ! G_k+b (ipol,ik,ib)
integer, allocatable :: ig_(:,:) ! G_k+b (ipol,ik,ib)
integer, allocatable :: lw(:,:), mw(:,:) ! l and m of wannier (16,n_wannier)
integer, allocatable :: num_sph(:) ! num. func. in lin. comb., (n_wannier)
logical, allocatable :: excluded_band(:)
integer :: iun_nnkp, iun_mmn, iun_amn, iun_band, iun_spn, iun_plot, iun_parity, nnbx, nexband
integer :: n_wannier !number of WF
integer :: n_proj !number of projection (=#WF unless spinors then =#WF/2)
complex(DP), allocatable :: gf(:,:) ! guding_function(npwx,n_wannier)
integer :: ispinw, ikstart, ikstop, iknum
character(LEN=15) :: wan_mode ! running mode
logical :: logwann, wvfn_formatted, write_unk, &
write_amn, write_mmn, reduce_unk, write_spn, write_unkg
! input data from nnkp file
real(DP), allocatable :: center_w(:,:) ! center_w(3,n_wannier)
integer, allocatable :: l_w(:), mr_w(:) ! l and mr of wannier (n_wannier) as from table 3.1,3.2 of spec.
integer, allocatable :: r_w(:) ! index of radial function (n_wannier) as from table 3.3 of spec.
real(DP), allocatable :: xaxis(:,:),zaxis(:,:) ! xaxis and zaxis(3,n_wannier)
real(DP), allocatable :: alpha_w(:) ! alpha_w(n_wannier) ( called zona in wannier spec)
!
real(DP), allocatable :: csph(:,:) ! expansion coefficients of gf on QE ylm function (16,n_wannier)
CHARACTER(len=256) :: seedname = 'wannier' ! prepended to file names in wannier90
! For implementation of wannier_lib
integer :: mp_grid(3) ! dimensions of MP k-point grid
real(DP) :: rlatt(3,3),glatt(3,3) ! real and recip lattices (Cartesian co-ords, units of Angstrom)
real(DP), allocatable :: kpt_latt(:,:) ! k-points in crystal co-ords. kpt_latt(3,iknum)
real(DP), allocatable :: atcart(:,:) ! atom centres in Cartesian co-ords and Angstrom units. atcart(3,nat)
integer :: num_bands ! number of bands left after exclusions
character(len=3), allocatable :: atsym(:) ! atomic symbols. atsym(nat)
integer :: num_nnmax=12
complex(DP), allocatable :: m_mat(:,:,:,:), a_mat(:,:,:)
complex(DP), allocatable :: u_mat(:,:,:), u_mat_opt(:,:,:)
logical, allocatable :: lwindow(:,:)
real(DP), allocatable :: wann_centers(:,:),wann_spreads(:)
real(DP) :: spreads(3)
real(DP), allocatable :: eigval(:,:)
end module wannier
!