mirror of
https://github.com/pfloos/quack
synced 2024-11-04 13:13:51 +01:00
hybrids
This commit is contained in:
parent
722d74ae17
commit
de4927aad4
@ -6,14 +6,14 @@
|
|||||||
# GGA = 2: B88,G96,PBE
|
# GGA = 2: B88,G96,PBE
|
||||||
# MGGA = 3:
|
# MGGA = 3:
|
||||||
# Hybrid = 4: HF,B3,PBE
|
# Hybrid = 4: HF,B3,PBE
|
||||||
4 B3
|
4 HF
|
||||||
# correlation rung:
|
# correlation rung:
|
||||||
# Hartree = 0: H
|
# Hartree = 0: H
|
||||||
# LDA = 1: VWN5,eVWN5
|
# LDA = 1: VWN5,eVWN5
|
||||||
# GGA = 2: LYP,PBE
|
# GGA = 2: LYP,PBE
|
||||||
# MGGA = 3:
|
# MGGA = 3:
|
||||||
# Hybrid = 4: HF,B88,PBE
|
# Hybrid = 4: HF,LYP,PBE
|
||||||
4 LYP
|
4 HF
|
||||||
# quadrature grid SG-n
|
# quadrature grid SG-n
|
||||||
1
|
1
|
||||||
# Number of states in ensemble (nEns)
|
# Number of states in ensemble (nEns)
|
||||||
|
@ -42,19 +42,19 @@ subroutine unrestricted_correlation_derivative_discontinuity(rung,DFA,nEns,wEns,
|
|||||||
|
|
||||||
case(2)
|
case(2)
|
||||||
|
|
||||||
call print_warning('!!! derivative discontinuity NYI for GGAs !!!')
|
call unrestricted_gga_correlation_derivative_discontinuity(DFA,nEns,wEns,nGrid,weight,rhow,Ec)
|
||||||
|
|
||||||
! MGGA functionals
|
! MGGA functionals
|
||||||
|
|
||||||
case(3)
|
case(3)
|
||||||
|
|
||||||
call print_warning('!!! derivative discontinuity NYI for MGGAs !!!')
|
call unrestricted_mgga_correlation_derivative_discontinuity(DFA,nEns,wEns,nGrid,weight,rhow,Ec)
|
||||||
|
|
||||||
! Hybrid functionals
|
! Hybrid functionals
|
||||||
|
|
||||||
case(4)
|
case(4)
|
||||||
|
|
||||||
call print_warning('!!! derivative discontinuity NYI for hybrids !!!')
|
call unrestricted_hybrid_correlation_derivative_discontinuity(DFA,nEns,wEns,nGrid,weight,rhow,Ec)
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
|
@ -59,7 +59,8 @@ subroutine unrestricted_exchange_derivative_discontinuity(rung,DFA,nEns,wEns,aCC
|
|||||||
|
|
||||||
case(4)
|
case(4)
|
||||||
|
|
||||||
call print_warning('!!! exchange part of derivative discontinuity NYI for hybrids !!!')
|
call unrestricted_hybrid_exchange_derivative_discontinuity(DFA,nEns,wEns(:),aCC_w1,aCC_w2,nGrid,weight(:),&
|
||||||
|
rhow(:),Cx_choice,doNcentered,kappa,ExDD(:))
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
|
@ -0,0 +1,44 @@
|
|||||||
|
subroutine unrestricted_gga_correlation_derivative_discontinuity(DFA,nEns,wEns,nGrid,weight,rhow,Ec)
|
||||||
|
|
||||||
|
! Compute the correlation GGA part of the derivative discontinuity
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
double precision,intent(in) :: rhow(nGrid,nspin)
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
double precision :: aC
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: Ec(nsp,nEns)
|
||||||
|
|
||||||
|
! Select correlation functional
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case ('LYP')
|
||||||
|
|
||||||
|
Ec(:,:) = 0d0
|
||||||
|
|
||||||
|
case ('PBE')
|
||||||
|
|
||||||
|
Ec(:,:) = 0d0
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! GGA correlation functional not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_gga_correlation_derivative_discontinuity
|
@ -0,0 +1,48 @@
|
|||||||
|
subroutine unrestricted_hybrid_correlation_derivative_discontinuity(DFA,nEns,wEns,nGrid,weight,rhow,Ec)
|
||||||
|
|
||||||
|
! Compute the correlation hybrid part of the derivative discontinuity
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
double precision,intent(in) :: rhow(nGrid,nspin)
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
double precision :: aC
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: Ec(nsp,nEns)
|
||||||
|
|
||||||
|
! Select correlation functional
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case ('HF')
|
||||||
|
|
||||||
|
Ec(:,:) = 0d0
|
||||||
|
|
||||||
|
case ('LYP')
|
||||||
|
|
||||||
|
Ec(:,:) = 0d0
|
||||||
|
|
||||||
|
case ('PBE')
|
||||||
|
|
||||||
|
Ec(:,:) = 0d0
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! Hybrid correlation functional not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_hybrid_correlation_derivative_discontinuity
|
56
src/eDFT/unrestricted_hybrid_correlation_energy.f90
Normal file
56
src/eDFT/unrestricted_hybrid_correlation_energy.f90
Normal file
@ -0,0 +1,56 @@
|
|||||||
|
subroutine unrestricted_hybrid_correlation_energy(DFA,nEns,wEns,nGrid,weight,rho,drho,Ec)
|
||||||
|
|
||||||
|
! Compute the unrestricted version of the correlation energy for hybrid functionals
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
double precision,intent(in) :: rho(nGrid,nspin)
|
||||||
|
double precision,intent(in) :: drho(ncart,nGrid,nspin)
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
double precision :: EcLDA(nsp)
|
||||||
|
double precision :: EcGGA(nsp)
|
||||||
|
double precision :: aC
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: Ec(nsp)
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case('HF')
|
||||||
|
|
||||||
|
Ec(:) = 0d0
|
||||||
|
|
||||||
|
case('LYP')
|
||||||
|
|
||||||
|
aC = 0.81d0
|
||||||
|
|
||||||
|
call unrestricted_lda_correlation_energy('VWN5 ',nEns,wEns,nGrid,weight,rho,EcLDA)
|
||||||
|
call unrestricted_gga_correlation_energy('LYP ',nEns,wEns,nGrid,weight,rho,drho,EcGGA)
|
||||||
|
|
||||||
|
Ec(:) = EcLDA(:) + aC*(EcGGA(:) - EcLDA(:))
|
||||||
|
|
||||||
|
case('PBE')
|
||||||
|
|
||||||
|
call unrestricted_gga_correlation_energy('PBE ',nEns,wEns,nGrid,weight,rho,drho,EcGGA)
|
||||||
|
|
||||||
|
Ec(:) = EcGGA(:)
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! Hybrid correlation energy not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_hybrid_correlation_energy
|
65
src/eDFT/unrestricted_hybrid_correlation_potential.f90
Normal file
65
src/eDFT/unrestricted_hybrid_correlation_potential.f90
Normal file
@ -0,0 +1,65 @@
|
|||||||
|
subroutine unrestricted_hybrid_correlation_potential(DFA,nEns,wEns,nGrid,weight,nBas,AO,dAO,rho,drho,Fc)
|
||||||
|
|
||||||
|
! Compute the correlation potential for hybrid functionals
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
integer,intent(in) :: nBas
|
||||||
|
double precision,intent(in) :: AO(nBas,nGrid)
|
||||||
|
double precision,intent(in) :: dAO(ncart,nBas,nGrid)
|
||||||
|
double precision,intent(in) :: rho(nGrid,nspin)
|
||||||
|
double precision,intent(in) :: drho(ncart,nGrid,nspin)
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
double precision,allocatable :: FcLDA(:,:,:)
|
||||||
|
double precision,allocatable :: FcGGA(:,:,:)
|
||||||
|
double precision :: aC
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: Fc(nBas,nBas,nspin)
|
||||||
|
|
||||||
|
! Memory allocation
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case('HF')
|
||||||
|
|
||||||
|
Fc(:,:,:) = 0d0
|
||||||
|
|
||||||
|
case('LYP')
|
||||||
|
|
||||||
|
allocate(FcLDA(nBas,nBas,nspin),FcGGA(nBas,nBas,nspin))
|
||||||
|
|
||||||
|
aC = 0.81d0
|
||||||
|
|
||||||
|
call unrestricted_lda_correlation_potential('VWN5 ',nEns,wEns,nGrid,weight,nBas,AO,rho,FcLDA)
|
||||||
|
call unrestricted_gga_correlation_potential('LYP ',nEns,wEns,nGrid,weight,nBas,AO,dAO,rho,drho,FcGGA)
|
||||||
|
|
||||||
|
Fc(:,:,:) = FcLDA(:,:,:) + aC*(FcGGA(:,:,:) - FcLDA(:,:,:))
|
||||||
|
|
||||||
|
case('PBE')
|
||||||
|
|
||||||
|
allocate(FcGGA(nBas,nBas,nspin))
|
||||||
|
|
||||||
|
call unrestricted_gga_correlation_potential('PBE ',nEns,wEns,nGrid,weight,nBas,AO,dAO,rho,drho,FcGGA)
|
||||||
|
|
||||||
|
Fc(:,:,:) = FcGGA(:,:,:)
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! Hybrid correlation potential not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_hybrid_correlation_potential
|
@ -0,0 +1,54 @@
|
|||||||
|
subroutine unrestricted_hybrid_exchange_derivative_discontinuity(DFA,nEns,wEns,aCC_w1,aCC_w2,nGrid,weight,rhow,&
|
||||||
|
Cx_choice,doNcentered,kappa,ExDD)
|
||||||
|
|
||||||
|
! Compute the exchange part of the derivative discontinuity for hybrid functionals
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
double precision,intent(in) :: aCC_w1(3)
|
||||||
|
double precision,intent(in) :: aCC_w2(3)
|
||||||
|
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
double precision,intent(in) :: rhow(nGrid)
|
||||||
|
integer,intent(in) :: Cx_choice
|
||||||
|
logical,intent(in) :: doNcentered
|
||||||
|
double precision,intent(in) :: kappa(nEns)
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: ExDD(nEns)
|
||||||
|
|
||||||
|
! Select exchange functional
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case ('HF')
|
||||||
|
|
||||||
|
ExDD(:) = 0d0
|
||||||
|
|
||||||
|
case ('B3')
|
||||||
|
|
||||||
|
ExDD(:) = 0d0
|
||||||
|
|
||||||
|
case ('PBE')
|
||||||
|
|
||||||
|
ExDD(:) = 0d0
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! Hybrid exchange derivative discontinuity not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_hybrid_exchange_derivative_discontinuity
|
69
src/eDFT/unrestricted_hybrid_exchange_energy.f90
Normal file
69
src/eDFT/unrestricted_hybrid_exchange_energy.f90
Normal file
@ -0,0 +1,69 @@
|
|||||||
|
subroutine unrestricted_hybrid_exchange_energy(DFA,LDA_centered,nEns,wEns,aCC_w1,aCC_w2,nGrid,weight,nBas,P,FxHF, &
|
||||||
|
rho,drho,Ex,Cx_choice)
|
||||||
|
|
||||||
|
! Compute the exchange energy for hybrid functionals
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
logical,intent(in) :: LDA_centered
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
double precision,intent(in) :: aCC_w1(3)
|
||||||
|
double precision,intent(in) :: aCC_w2(3)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
integer,intent(in) :: nBas
|
||||||
|
double precision,intent(in) :: P(nBas,nBas)
|
||||||
|
double precision,intent(in) :: FxHF(nBas,nBas)
|
||||||
|
double precision,intent(in) :: rho(nGrid)
|
||||||
|
double precision,intent(in) :: drho(ncart,nGrid)
|
||||||
|
integer,intent(in) :: Cx_choice
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
double precision :: ExLDA,ExGGA,ExHF
|
||||||
|
double precision :: a0,aX
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: Ex
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case ('HF')
|
||||||
|
|
||||||
|
call unrestricted_fock_exchange_energy(nBas,P,FxHF,Ex)
|
||||||
|
|
||||||
|
case ('B3')
|
||||||
|
|
||||||
|
a0 = 0.20d0
|
||||||
|
aX = 0.72d0
|
||||||
|
|
||||||
|
call unrestricted_lda_exchange_energy('S51 ',LDA_centered,nEns,wEns,aCC_w1,aCC_w2,nGrid,weight,&
|
||||||
|
rho,ExLDA,Cx_choice)
|
||||||
|
call unrestricted_gga_exchange_energy('B88 ',nEns,wEns,nGrid,weight,rho,drho,ExGGA)
|
||||||
|
call unrestricted_fock_exchange_energy(nBas,P,FxHF,ExHF)
|
||||||
|
|
||||||
|
Ex = ExLDA &
|
||||||
|
+ a0*(ExHF - ExLDA) &
|
||||||
|
+ aX*(ExGGA - ExLDA)
|
||||||
|
|
||||||
|
case ('PBE')
|
||||||
|
|
||||||
|
call unrestricted_gga_exchange_energy('PBE ',nEns,wEns,nGrid,weight,rho,drho,ExGGA)
|
||||||
|
call unrestricted_fock_exchange_energy(nBas,P,FxHF,ExHF)
|
||||||
|
|
||||||
|
Ex = 0.25d0*ExHF + 0.75d0*ExGGA
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! Hybrid exchange energy not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_hybrid_exchange_energy
|
78
src/eDFT/unrestricted_hybrid_exchange_potential.f90
Normal file
78
src/eDFT/unrestricted_hybrid_exchange_potential.f90
Normal file
@ -0,0 +1,78 @@
|
|||||||
|
subroutine unrestricted_hybrid_exchange_potential(DFA,LDA_centered,nEns,wEns,aCC_w1,aCC_w2,nGrid,weight,nBas,P, &
|
||||||
|
ERI,AO,dAO,rho,drho,Fx,FxHF,Cx_choice)
|
||||||
|
|
||||||
|
! Compute the exchange potential for hybrid functionals
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
logical,intent(in) :: LDA_centered
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
double precision,intent(in) :: aCC_w1(3)
|
||||||
|
double precision,intent(in) :: aCC_w2(3)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
integer,intent(in) :: nBas
|
||||||
|
double precision,intent(in) :: P(nBas,nBas)
|
||||||
|
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
|
||||||
|
double precision,intent(in) :: AO(nBas,nGrid)
|
||||||
|
double precision,intent(in) :: dAO(ncart,nBas,nGrid)
|
||||||
|
double precision,intent(in) :: rho(nGrid)
|
||||||
|
double precision,intent(in) :: drho(ncart,nGrid)
|
||||||
|
integer,intent(in) :: Cx_choice
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
double precision,allocatable :: FxLDA(:,:),FxGGA(:,:)
|
||||||
|
double precision :: a0,aX
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: Fx(nBas,nBas),FxHF(nBas,nBas)
|
||||||
|
|
||||||
|
! Memory allocation
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case('HF')
|
||||||
|
|
||||||
|
call unrestricted_fock_exchange_potential(nBas,P,ERI,FxHF)
|
||||||
|
Fx(:,:) = FxHF(:,:)
|
||||||
|
|
||||||
|
case('B3')
|
||||||
|
|
||||||
|
allocate(FxLDA(nBas,nBas),FxGGA(nBas,nBas))
|
||||||
|
|
||||||
|
a0 = 0.20d0
|
||||||
|
aX = 0.72d0
|
||||||
|
|
||||||
|
call unrestricted_lda_exchange_potential('S51 ',LDA_centered,nEns,wEns,aCC_w1,aCC_w2,nGrid,weight, &
|
||||||
|
nBas,AO,rho,FxLDA,Cx_choice)
|
||||||
|
call unrestricted_gga_exchange_potential('B88 ',nEns,wEns,nGrid,weight,nBas,AO,dAO,rho,drho,FxGGA)
|
||||||
|
call unrestricted_fock_exchange_potential(nBas,P,ERI,FxHF)
|
||||||
|
|
||||||
|
Fx(:,:) = FxLDA(:,:) &
|
||||||
|
+ a0*(FxHF(:,:) - FxLDA(:,:)) &
|
||||||
|
+ aX*(FxGGA(:,:) - FxLDA(:,:))
|
||||||
|
|
||||||
|
case('PBE')
|
||||||
|
|
||||||
|
allocate(FxGGA(nBas,nBas))
|
||||||
|
|
||||||
|
call unrestricted_gga_exchange_potential('PBE ',nEns,wEns,nGrid,weight,nBas,AO,dAO,rho,drho,FxGGA)
|
||||||
|
call unrestricted_fock_exchange_potential(nBas,P,ERI,FxHF)
|
||||||
|
|
||||||
|
Fx(:,:) = 0.25d0*FxHF(:,:) + 0.75d0*FxGGA(:,:)
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! Hybrid exchange potential not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_hybrid_exchange_potential
|
@ -0,0 +1,34 @@
|
|||||||
|
subroutine unrestricted_mgga_correlation_derivative_discontinuity(DFA,nEns,wEns,nGrid,weight,rhow,Ec)
|
||||||
|
|
||||||
|
! Compute the correlation MGGA part of the derivative discontinuity
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
double precision,intent(in) :: rhow(nGrid,nspin)
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision,intent(out) :: Ec(nsp,nEns)
|
||||||
|
|
||||||
|
! Select correlation functional
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! MGGA correlation functional not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_mgga_correlation_derivative_discontinuity
|
36
src/eDFT/unrestricted_mgga_correlation_energy.f90
Normal file
36
src/eDFT/unrestricted_mgga_correlation_energy.f90
Normal file
@ -0,0 +1,36 @@
|
|||||||
|
subroutine unrestricted_mgga_correlation_energy(DFA,nEns,wEns,nGrid,weight,rho,drho,Ec)
|
||||||
|
|
||||||
|
! Compute unrestricted MGGA correlation energy
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
include 'parameters.h'
|
||||||
|
|
||||||
|
! Input variables
|
||||||
|
|
||||||
|
character(len=12),intent(in) :: DFA
|
||||||
|
integer,intent(in) :: nEns
|
||||||
|
double precision,intent(in) :: wEns(nEns)
|
||||||
|
integer,intent(in) :: nGrid
|
||||||
|
double precision,intent(in) :: weight(nGrid)
|
||||||
|
double precision,intent(in) :: rho(nGrid,nspin)
|
||||||
|
double precision,intent(in) :: drho(ncart,nGrid,nspin)
|
||||||
|
|
||||||
|
! Local variables
|
||||||
|
|
||||||
|
integer :: iG
|
||||||
|
double precision :: ra,rb,ga,gb
|
||||||
|
|
||||||
|
! Output variables
|
||||||
|
|
||||||
|
double precision :: Ec(nsp)
|
||||||
|
|
||||||
|
select case (DFA)
|
||||||
|
|
||||||
|
case default
|
||||||
|
|
||||||
|
call print_warning('!!! MGGA correlation energy not available !!!')
|
||||||
|
stop
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine unrestricted_mgga_correlation_energy
|
Loading…
Reference in New Issue
Block a user