! ! Copyright (C) 2002-2005 FPMD-CPV groups ! 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 bhs ! analytical BHS pseudopotential parameters use parameters, only: nsx implicit none save real(8) :: rc1(nsx), rc2(nsx), wrc1(nsx), wrc2(nsx), & rcl(3,nsx,3), al(3,nsx,3), bl(3,nsx,3) integer :: lloc(nsx) end module bhs ! f = occupation numbers ! qbac = background neutralizing charge ! nspin = number of spins (1=no spin, 2=LSDA) ! nel(nspin) = number of electrons (up, down) ! nupdwn= number of states with spin up (1) and down (2) ! iupdwn= first state with spin (1) and down (2) ! n = total number of electronic states ! nx = if n is even, nx=n ; if it is odd, nx=n+1 ! nx is used only to dimension arrays ! ispin = spin of each state ! ! tpiba = 2*pi/alat ! tpiba2 = (2*pi/alat)**2 ! ng = number of G vectors for density and potential ! ngl = number of shells of G ! G-vector quantities for the thick grid - see also doc in ggen ! g = G^2 in increasing order (in units of tpiba2=(2pi/a)^2) ! gl = shells of G^2 ( " " " " " ) ! gx = G-vectors ( " " " tpiba =(2pi/a) ) ! ! g2_g = all G^2 in increasing order, replicated on all procs ! mill_g = miller index of G vecs (increasing order), replicated on all procs ! mill_l = miller index of G vecs local to the processors ! ig_l2g = "l2g" means local to global, this array convert a local ! G-vector index into the global index, in other words ! the index of the G-v. in the overall array of G-vectors ! bi? = base vector used to generate the reciprocal space ! ! np = fft index for G> ! nm = fft index for G< ! mill_l = G components in crystal axis ! ! ! lqmax: maximum angular momentum of Q (Vanderbilt augmentation charges) ! nqfx : maximum number of coefficients in Q smoothing ! nbrx : maximum number of distinct radial beta functions ! ndmx: maximum number of points in the radial grid ! ! nbeta number of beta functions (sum over all l) ! kkbeta last radial mesh point used to describe functions ! which vanish outside core ! nqf coefficients in Q smoothing ! nqlc angular momenta present in Q smoothing ! lll lll(j) is l quantum number of j'th beta function ! lmaxq highest angular momentum that is present in Q functions ! lmaxkb highest angular momentum that is present in beta functions ! dion bare pseudopotential D_{\mu,\nu} parameters ! (ionic and screening parts subtracted out) ! betar the beta function on a r grid (actually, r*beta) ! qqq Q_ij matrix ! qfunc Q_ij(r) function (for r>rinner) ! rinner radius at which to cut off partial core or Q_ij ! ! qfcoef coefficients to pseudize qfunc for different total ! angular momentum (for r**(-1) ! first index: orbital ! second index: atomic species REAL(DP), ALLOCATABLE :: wnl(:,:,:,:) ! Kleinman-Bylander products ! ! first index: G vector ! second index: orbital ! third index: atomic species ! fourth index: k point CONTAINS SUBROUTINE allocate_ncpp( nsp, ngw, nbetax, nhm, nk ) INTEGER, INTENT(IN) :: nsp, nbetax, nhm, ngw, nk INTEGER :: ierr ALLOCATE( wnl( ngw, nbetax, nsp, nk ), STAT=ierr) IF( ierr /= 0 ) CALL errore(' allocate_ncpp ', ' allocating wnl ', ierr ) ALLOCATE( wsg( nhm, nsp ), STAT=ierr) IF( ierr /= 0 ) CALL errore(' allocate_ncpp ', ' allocating wsg ', ierr ) RETURN END SUBROUTINE allocate_ncpp SUBROUTINE deallocate_ncpp IF( ALLOCATED( wsg ) ) DEALLOCATE( wsg ) IF( ALLOCATED( wnl ) ) DEALLOCATE( wnl ) RETURN END SUBROUTINE deallocate_ncpp END MODULE ncpp module cvan ! this file contains common subroutines and modules between ! CP and FPMD ! ionic pseudo-potential variables use parameters, only: nsx implicit none save integer nvb, ish(nsx) ! nvb = number of species with Vanderbilt PPs ! ish(is)= used for indexing the nonlocal projectors betae ! with contiguous indices inl=ish(is)+(iv-1)*na(is)+1 ! where "is" is the species and iv=1,nh(is) ! ! indlm: indlm(ind,is)=Y_lm for projector ind integer, allocatable:: indlm(:,:) contains subroutine allocate_cvan( nind, ns ) integer, intent(in) :: nind, ns allocate( indlm( nind, ns ) ) end subroutine allocate_cvan subroutine deallocate_cvan( ) if( allocated(indlm) ) deallocate( indlm ) end subroutine deallocate_cvan end module cvan