some small corrections

This commit is contained in:
fabrizio22 2019-05-08 17:29:58 +02:00
parent c9f41a164b
commit d60e77510d
3 changed files with 18 additions and 16 deletions

View File

@ -315,9 +315,6 @@ module funct
!
integer, parameter:: notset = -1
!
! switches to decide between qe (1) and libxc (2) routines
integer :: qe_or_libxc(2)
!
! internal indices for exchange-correlation
! iexch: type of exchange
! icorr: type of correlation
@ -331,6 +328,15 @@ module funct
integer :: igcc = notset
integer :: imeta = notset
integer :: inlc = notset
!
! Switches to decide between qe (1) and libxc (2) routines for each single xc term
! (only LDA at present)
! PROVISIONAL: probably it should be put as an environment variable or something
#if defined(__LIBXC)
integer :: qe_or_libxc(1:2) = 1
#else
integer :: qe_or_libxc(1:2) = 0
#endif
!
real(DP):: exx_fraction = 0.0_DP
real(DP):: screening_parameter = 0.0_DP
@ -411,14 +417,6 @@ CONTAINS
do l = 1, len
dftout (l:l) = capital (dft_(l:l) )
enddo
!
!
! PROVISIONAL: it should be put as an environment variable or something
qe_or_libxc(:)=0
#if defined(__LIBXC)
qe_or_libxc(1)=1
qe_or_libxc(2)=1
#endif
!
! ----------------------------------------------
! FIRST WE CHECK ALL THE SHORT NAMES
@ -2915,8 +2913,9 @@ return
end subroutine tau_xc_array_spin
!
!
!-----------------------------------------------------------------------
SUBROUTINE init_lda_xc()
!-------------------------------------------------------------------
!! Gets from inside parameters needed to initialize lda xc-drivers.
!
USE kinds, ONLY: DP
@ -2935,6 +2934,9 @@ SUBROUTINE init_lda_xc()
icorr_l = get_icorr()
IF (libxc_switches(2)==1) icorr_l = qe_to_libxc_index( icorr, 'corr_LDA' )
!
IF (iexch_l==-1 .OR. icorr_l==-1) CALL errore( 'init_lda_xc', 'Functional &
& indexes not well defined', 1 )
!
! hybrid exchange vars
exx_started_l = exx_is_active()
exx_fraction_l = 0._DP

View File

@ -73,9 +73,9 @@ SUBROUTINE select_lda_functionals( iexch, icorr, exx_fraction, finite_size_cell_
END SUBROUTINE select_lda_functionals
!
!
!---------------------------------------------------------------------
!---------------------------------------------------------------------------
SUBROUTINE xc( length, sr_d, sv_d, rho_in, ex_out, ec_out, vx_out, vc_out )
!---------------------------------------------------------------------
!-------------------------------------------------------------------------
!! Wrapper routine. Calls xc-driver routines from internal libraries
!! of q-e or from the external libxc, depending on the input choice.
!

View File

@ -336,7 +336,7 @@ PROGRAM do_ppacf
IF (arhox(1) > vanishing_charge) THEN
IF(iexch==1) THEN
rs = pi34 /arhox**third
CALL slater(1, rs, ex, vx(:,1)) ! \epsilon_x,\lambda[n]=\epsilon_x[n]
CALL slater( rs, ex(1), vx(1,1)) ! \epsilon_x,\lambda[n]=\epsilon_x[n]
ELSE
CALL xc_lda( 1, arhox, ex, ec, vx(:,1), vc(:,1) )
ENDIF
@ -416,7 +416,7 @@ PROGRAM do_ppacf
IF( ABS( zeta(1) ) > 1.D0 ) zeta(1) = SIGN(1.D0, zeta(1))
IF(iexch==1) THEN
!
CALL slater_spin(1, arhox, zeta, ex, vx)
CALL slater_spin(arhox(1), zeta(1), ex(1), vx(1,:))
!
ELSE
CALL xc_lsda( 1, arhox, zeta, ex, ec, vx, vc )