quantum-espresso/Modules/wannier_new.f90

65 lines
2.3 KiB
Fortran

! Copyright (C) 2006-2008 Dmitry Korotin - dmitry@korotin.name
! 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_new
!
!! Variables to construct and store wannier functions
!
USE kinds, ONLY : DP
!
SAVE
!
INTEGER, PARAMETER :: ningx = 10
!! max number of trial wavefunction ingredients
LOGICAL :: use_wannier
!! if .TRUE. wannier functions are constructed
LOGICAL :: rkmesh
!! if .TRUE. regular k-mesh without symmetry is used !now used in input_parameters_mod
LOGICAL :: plot_wannier
!! if .TRUE. wannier number plot_wan_num is plotted
LOGICAL :: use_energy_int
!! if .TRUE. uses energy interval for wannier generation, not band numbers
LOGICAL :: print_wannier_coeff
!! if .TRUE. computes and prints coefficients of wannier decomp. on atomic functions
INTEGER :: nwan
!! number of wannier functions
INTEGER :: plot_wan_num
!! number of wannier for plotting
INTEGER :: plot_wan_spin
!! spin of wannier for plotting
REAL(kind=DP), allocatable :: wan_pot(:,:)
!! constrained potential
REAL(kind=DP), allocatable :: wannier_energy(:,:)
!! energy of each wannier (of each spin)
REAL(kind=DP), allocatable :: wannier_occ(:,:,:)
!! occupation matrix of wannier functions(of each spin)
COMPLEX(kind=DP), allocatable :: pp(:,:)
!! <phi|S|psi> projections
COMPLEX(kind=DP), allocatable :: coef(:,:,:)
!! coefficients of wannier decomp. on atomic functions
TYPE ingredient
INTEGER :: l = 0, & ! l value for atomic wfc
m = 0, & ! m value for atomic wfc
iatomwfc = 0 ! number of corresponding atomic orbital
REAL :: c = 0.d0 ! coefficient
END TYPE ingredient
TYPE wannier_data
INTEGER :: iatom = 0, &
ning = 0
REAL :: bands_from = 0.d0, &
bands_to = 0.d0
TYPE (ingredient) :: ing(ningx)
END TYPE wannier_data
TYPE (wannier_data), allocatable :: wan_in(:,:)
END MODULE wannier_new