libxc-more - possible qe-libxc conflicts fixed in atomic

This commit is contained in:
fabrizio22 2021-06-08 15:53:33 +02:00
parent 81882f1680
commit fab58b00f4
6 changed files with 23 additions and 21 deletions

View File

@ -18,7 +18,7 @@ subroutine elsd ( zed, grid, rho, vxt, vh, vxc, exc, excgga, nwf,&
use kinds, only : DP
use constants, only: fpi
use radial_grids, only: ndmx, radial_grid_type
use xc_lib, only: xclib_get_id, xclib_dft_is
use xc_lib, only: xclib_get_id, xclib_dft_is, xclib_dft_is_libxc
use ld1inc, only: vx, noscf, tau, vtau
implicit none
integer, intent(in) :: nwf, nspin
@ -34,8 +34,8 @@ subroutine elsd ( zed, grid, rho, vxt, vh, vxc, exc, excgga, nwf,&
logical:: oep, meta, kli
if (noscf) return
oep = xclib_get_id('LDA','EXCH').eq.4
kli = xclib_get_id('LDA','EXCH').eq.10
oep = xclib_get_id('LDA','EXCH')== 4 .and. .not.xclib_dft_is_libxc('LDA','EXCH')
kli = xclib_get_id('LDA','EXCH')==10 .and. .not.xclib_dft_is_libxc('LDA','EXCH')
meta = xclib_dft_is('meta')

View File

@ -25,7 +25,7 @@ SUBROUTINE ld1_setup
nwfts, nnts, llts, jjts, elts, iswts, octs, nstoaets, &
nwftsc, nntsc, lltsc, jjtsc, eltsc, iswtsc, octsc, nstoaec, lpaw
USE funct, ONLY : dft_is_nonlocc
USE xc_lib, ONLY : xclib_get_id, xclib_dft_is, start_exx
USE xc_lib, ONLY : xclib_get_id, xclib_dft_is, xclib_dft_is_libxc, start_exx
!
IMPLICIT NONE
@ -41,9 +41,9 @@ SUBROUTINE ld1_setup
CALL errore('ld1_setup','meta-GGA not implemented for LSDA', 2)
IF ( meta .and. iswitch > 1 ) &
CALL errore('ld1_setup','meta-GGA implemented only for all-electron case', 3)
hf = xclib_get_id('LDA','EXCH')==5
hf = xclib_get_id('LDA','EXCH')==5 .and. .not.xclib_dft_is_libxc('LDA','EXCH')
IF (hf) CALL errore('ld1_setup','HF not implemented yet',1)
oep = xclib_get_id('LDA','EXCH')==4
oep = xclib_get_id('LDA','EXCH')==4 .and. .not.xclib_dft_is_libxc('LDA','EXCH')
IF (oep.and.iswitch>1) &
CALL errore('ld1_setup','OEP is implemented only for all-electron calc.',1)
IF (oep.and.rel>0) &

View File

@ -16,7 +16,7 @@ subroutine new_potential &
use constants, only: fpi, e2
use radial_grids, only: radial_grid_type, hartree
use kinds, only : DP
use xc_lib, only: xclib_get_id, xclib_dft_is
use xc_lib, only: xclib_get_id, xclib_dft_is, xclib_dft_is_libxc
use ld1inc, only : nwf, vx, vxc, exc, excgga, tau, vtau
use kli, only : compute_kli_potential
implicit none
@ -37,8 +37,8 @@ subroutine new_potential &
gga = xclib_dft_is('gradient')
meta = xclib_dft_is('meta')
oep = xclib_get_id('LDA','EXCH').eq.4
kli_= xclib_get_id('LDA','EXCH').eq.10
oep = xclib_get_id('LDA','EXCH')== 4 .and. (.not.xclib_dft_is_libxc('LDA','EXCH'))
kli_= xclib_get_id('LDA','EXCH')==10 .and. (.not.xclib_dft_is_libxc('LDA','EXCH'))
nspin = 1
if (lsd.eq.1) nspin = 2

View File

@ -14,7 +14,7 @@ subroutine v_of_rho_at (rho,rhoc,vh,vxc,exc,excgga,vnew,nlcc,iflag)
use kinds, only : DP
use constants, only: fpi, e2
use radial_grids, only: ndmx, hartree
use xc_lib, only: xclib_get_id, xclib_dft_is
use xc_lib, only: xclib_get_id, xclib_dft_is, xclib_dft_is_libxc
use ld1inc, only: nwf, grid, vx, vxt, lsd, zed, enne, latt, nspin
implicit none
integer, intent(in) :: iflag
@ -35,7 +35,7 @@ subroutine v_of_rho_at (rho,rhoc,vh,vxc,exc,excgga,vnew,nlcc,iflag)
real(DP),allocatable:: dchi0(:,:)
gga=xclib_dft_is('gradient')
oep=xclib_get_id('LDA','EXCH').eq.4
oep=xclib_get_id('LDA','EXCH')==4 .and. .not.xclib_dft_is_libxc('LDA','EXCH')
!
! compute hartree potential with the total charge
!

View File

@ -14,7 +14,7 @@ subroutine which_cpmd_dft &
!-----------------------------------------------------------------------
!
use funct, only : set_dft_from_name
use xc_lib, only : xclib_get_id
use xc_lib, only : xclib_get_id, xclib_dft_is_libxc
implicit none
character(len=*), intent(IN) :: dft
@ -27,12 +27,14 @@ subroutine which_cpmd_dft &
mgcc = xclib_get_id('GGA','CORR')
! in CPMD PW91 and LYP are swapped.
if (mgcc.eq.3) then
mgcc=2
else if (mgcc.eq.2) then
mgcc=3
end if
if (.not.xclib_dft_is_libxc('GGA','CORR')) then
if (mgcc.eq.3) then
mgcc=2
else if (mgcc.eq.2) then
mgcc=3
end if
endif
return
end subroutine which_cpmd_dft
!

View File

@ -23,7 +23,7 @@ subroutine write_results
relpert, evel, edar, eso, noscf, iswitch, rho, &
file_charge, max_out_wfc, vx
use funct, only : get_dft_name, write_dft_name
use xc_lib, only : xclib_get_id
use xc_lib, only : xclib_get_id, xclib_dft_is_libxc
implicit none
@ -64,8 +64,8 @@ subroutine write_results
1000 format(/5x, &
'n l nl e(Ry) ',' e(Ha) e(eV)')
oep = xclib_get_id('LDA','EXCH') .eq. 4
kli = xclib_get_id('LDA','EXCH') .eq. 10
oep = xclib_get_id('LDA','EXCH')== 4 .and. .not.xclib_dft_is_libxc('LDA','EXCH')
kli = xclib_get_id('LDA','EXCH')==10 .and. .not.xclib_dft_is_libxc('LDA','EXCH')
if (oep) enl(1:nwf) = enl(1:nwf) - enzero(isw(1:nwf))
do n=1,nwf
if (oc(n)>-eps6) then