Skip to content

Commit

Permalink
Merge pull request #393 from OrderN/f-libxc7.0.0
Browse files Browse the repository at this point in the history
F libxc7.0.0
  • Loading branch information
tsuyoshi38 authored Jan 14, 2025
2 parents b24500e + 57e93d7 commit 868ab6d
Show file tree
Hide file tree
Showing 4 changed files with 64 additions and 62 deletions.
70 changes: 35 additions & 35 deletions src/XC_LibXC_v5_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ module XC

use datatypes
use global_module, only: area_ops, io_lun, iprint_ops, spin_factor
use xc_f90_lib_m
use xc_f03_lib_m

implicit none

Expand All @@ -55,8 +55,8 @@ module XC
! LibXC variables
integer :: n_xc_terms
integer, dimension(2) :: i_xc_family
type(xc_f90_func_t), dimension(:), allocatable :: xc_func
type(xc_f90_func_info_t), dimension(:), allocatable :: xc_info
type(xc_f03_func_t), dimension(:), allocatable :: xc_func
type(xc_f03_func_info_t), dimension(:), allocatable :: xc_info
logical :: flag_use_libxc

! Conquest functional identifiers
Expand Down Expand Up @@ -113,8 +113,8 @@ subroutine init_xc
integer :: vmajor, vminor, vmicro, i, j
integer, dimension(2) :: xcpart
character(len=120) :: name, kind, family, ref
type(xc_f90_func_t) :: temp_xc_func
type(xc_f90_func_info_t) :: temp_xc_info
type(xc_f03_func_t) :: temp_xc_func
type(xc_f03_func_info_t) :: temp_xc_info

! Test for LibXC or CQ
if(flag_functional_type<0) then
Expand All @@ -123,7 +123,7 @@ subroutine init_xc
! LibXC functional specified
! --------------------------
flag_use_libxc = .true.
call xc_f90_version(vmajor, vminor, vmicro)
call xc_f03_version(vmajor, vminor, vmicro)
if(inode==ionode.AND.iprint_ops>0) then
if(vmajor>2) then
write(io_lun,'(4x,"LibXC version: ",I2,".",I2,".",I2)') vmajor, vminor, vmicro
Expand All @@ -141,39 +141,39 @@ subroutine init_xc
i = floor(-flag_functional_type/1000.0_double)
! Temporary init to find exchange or correlation
if(nspin==1) then
call xc_f90_func_init(temp_xc_func, i, XC_UNPOLARIZED)
temp_xc_info = xc_f90_func_get_info(temp_xc_func)
call xc_f03_func_init(temp_xc_func, i, XC_UNPOLARIZED)
temp_xc_info = xc_f03_func_get_info(temp_xc_func)
else if(nspin==2) then
call xc_f90_func_init(temp_xc_func, i, XC_POLARIZED)
temp_xc_info = xc_f90_func_get_info(temp_xc_func)
call xc_f03_func_init(temp_xc_func, i, XC_POLARIZED)
temp_xc_info = xc_f03_func_get_info(temp_xc_func)
end if
select case(xc_f90_func_info_get_kind(temp_xc_info))
select case(xc_f03_func_info_get_kind(temp_xc_info))
case(XC_EXCHANGE)
xcpart(1) = i
xcpart(2) = -flag_functional_type - xcpart(1)*1000
case(XC_CORRELATION)
xcpart(2) = i
xcpart(1) = -flag_functional_type - xcpart(2)*1000
end select
call xc_f90_func_end(temp_xc_func)
call xc_f03_func_end(temp_xc_func)
end if
! Now initialise and output
allocate(xc_func(n_xc_terms),xc_info(n_xc_terms))
do i=1,n_xc_terms
if(nspin==1) then
call xc_f90_func_init(xc_func(i), xcpart(i), XC_UNPOLARIZED)
xc_info(i) = xc_f90_func_get_info(xc_func(i))
call xc_f03_func_init(xc_func(i), xcpart(i), XC_UNPOLARIZED)
xc_info(i) = xc_f03_func_get_info(xc_func(i))
else if(nspin==2) then
call xc_f90_func_init(xc_func(i), xcpart(i), XC_POLARIZED)
xc_info(i) = xc_f90_func_get_info(xc_func(i))
call xc_f03_func_init(xc_func(i), xcpart(i), XC_POLARIZED)
xc_info(i) = xc_f03_func_get_info(xc_func(i))
end if
! Consistent threshold with Conquest
if(vmajor>2) call xc_f90_func_set_dens_threshold(xc_func(i),RD_ERR)
name = xc_f90_func_info_get_name(xc_info(i))
i_xc_family(i) = xc_f90_func_info_get_family(xc_info(i))
if(vmajor>2) call xc_f03_func_set_dens_threshold(xc_func(i),RD_ERR)
name = xc_f03_func_info_get_name(xc_info(i))
i_xc_family(i) = xc_f03_func_info_get_family(xc_info(i))
if(i_xc_family(i)==XC_FAMILY_GGA) flag_is_GGA = .true.
if(inode==ionode) then
select case(xc_f90_func_info_get_kind(xc_info(i)))
select case(xc_f03_func_info_get_kind(xc_info(i)))
case (XC_EXCHANGE)
write(kind, '(a)') 'an exchange functional'
case (XC_CORRELATION)
Expand Down Expand Up @@ -207,10 +207,10 @@ subroutine init_xc
& " family and is defined in the reference(s):")') &
trim(name), trim(kind), trim(family)
j = 0
ref = xc_f90_func_reference_get_ref(xc_f90_func_info_get_references(xc_info(i),j))
ref = xc_f03_func_reference_get_ref(xc_f03_func_info_get_references(xc_info(i),j))
do while(j >= 0)
write(io_lun, '(4x,a,i1,2a)') '[', j, '] ', trim(ref)
ref = xc_f90_func_reference_get_ref(xc_f90_func_info_get_references(xc_info(i),j))
ref = xc_f03_func_reference_get_ref(xc_f03_func_info_get_references(xc_info(i),j))
end do
else
write(io_lun,'(4x,"The functional ", a, " is ", a, ", and it belongs to the ", a, &
Expand All @@ -220,7 +220,7 @@ subroutine init_xc
else if(iprint_ops>0) then
write(io_lun,'(4x,"Using the ",a," functional ",a)') trim(family),trim(name)
else
select case(xc_f90_func_info_get_kind(xc_info(i)))
select case(xc_f03_func_info_get_kind(xc_info(i)))
case (XC_EXCHANGE)
write(io_lun,fmt='(/4x,"Using X functional ",a)') trim(name)
case (XC_CORRELATION)
Expand Down Expand Up @@ -318,10 +318,10 @@ subroutine write_xc_refs
write(io_lun,fmt='(4x,"XC references from LibXC:")')
do j=1,n_xc_terms
i = 0
ref = xc_f90_func_reference_get_ref(xc_f90_func_info_get_references(xc_info(j),i))
ref = xc_f03_func_reference_get_ref(xc_f03_func_info_get_references(xc_info(j),i))
do while(i >= 0)
write(io_lun, '(6x,a)') trim(ref)
ref = xc_f90_func_reference_get_ref(xc_f90_func_info_get_references(xc_info(j),i))
ref = xc_f03_func_reference_get_ref(xc_f03_func_info_get_references(xc_info(j),i))
end do
end do
return
Expand Down Expand Up @@ -700,10 +700,10 @@ subroutine get_libxc_potential(density, xc_potential, xc_epsilon, xc_energy, siz
if(nspin>1) then
select case( i_xc_family(nxc) )
case(XC_FAMILY_LDA)
call xc_f90_lda_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
call xc_f03_lda_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
alt_dens, eps, vrho )
case(XC_FAMILY_GGA)
call xc_f90_gga_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
call xc_f03_gga_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
alt_dens, sigma, eps, vrho, vsigma )
end select

Expand Down Expand Up @@ -784,10 +784,10 @@ subroutine get_libxc_potential(density, xc_potential, xc_epsilon, xc_energy, siz
else ! No spin
select case (i_xc_family(nxc))
case(XC_FAMILY_LDA)
call xc_f90_lda_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
call xc_f03_lda_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
alt_dens, eps, vrho )
case(XC_FAMILY_GGA)
call xc_f90_gga_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
call xc_f03_gga_exc_vxc( xc_func(nxc), int(n_my_grid_points,kind=wide), &
alt_dens, sigma, eps, vrho, vsigma )
end select

Expand Down Expand Up @@ -1007,7 +1007,7 @@ subroutine get_libxc_dpotential(density, dxc_potential, size, density_out)
if(nspin>1) then ! NB no spin-polarised GGA NSC forces
select case (i_xc_family(j))
case(XC_FAMILY_LDA)
call xc_f90_lda_fxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,vrho)
call xc_f03_lda_fxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,vrho)
dxc_potential(1:n_my_grid_points,1,1) = dxc_potential(:n_my_grid_points,1,1) +vrho(1:3*n_my_grid_points-2:3)
dxc_potential(1:n_my_grid_points,1,2) = dxc_potential(:n_my_grid_points,1,2) +vrho(2:3*n_my_grid_points-1:3)
dxc_potential(1:n_my_grid_points,2,1) = dxc_potential(:n_my_grid_points,2,1) +vrho(2:3*n_my_grid_points-1:3)
Expand All @@ -1016,13 +1016,13 @@ subroutine get_libxc_dpotential(density, dxc_potential, size, density_out)
else
select case (i_xc_family(j))
case(XC_FAMILY_LDA)
call xc_f90_lda_fxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,vrho)
call xc_f03_lda_fxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,vrho)
dxc_potential(1:n_my_grid_points,1,1) = dxc_potential(1:n_my_grid_points,1,1) + &
vrho(1:n_my_grid_points)
case(XC_FAMILY_GGA)
call xc_f90_gga_vxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,sigma,vrho,&
call xc_f03_gga_vxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,sigma,vrho,&
vsigma)
call xc_f90_gga_fxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,sigma,&
call xc_f03_gga_fxc(xc_func(j),int(n_my_grid_points,kind=wide),alt_dens,sigma,&
v2rho2,v2rhosigma,v2sigma2)
end select

Expand Down Expand Up @@ -1219,9 +1219,9 @@ subroutine get_libxc_energy(density, xc_energy, size)
eps = zero
select case( i_xc_family(nxc) )
case(XC_FAMILY_LDA)
call xc_f90_lda_exc( xc_func(nxc), int(n_my_grid_points,kind=wide), alt_dens, eps )
call xc_f03_lda_exc( xc_func(nxc), int(n_my_grid_points,kind=wide), alt_dens, eps )
case(XC_FAMILY_GGA)
call xc_f90_gga_exc( xc_func(nxc), int(n_my_grid_points,kind=wide), alt_dens, sigma, eps )
call xc_f03_gga_exc( xc_func(nxc), int(n_my_grid_points,kind=wide), alt_dens, sigma, eps )
end select
xc_epsilon(1:n_my_grid_points) = xc_epsilon(1:n_my_grid_points) + eps(1:n_my_grid_points)
end do ! nxc = n_xc_terms
Expand Down
5 changes: 3 additions & 2 deletions src/system/system.example.make
Original file line number Diff line number Diff line change
Expand Up @@ -31,10 +31,11 @@ SCALAPACK = -lscalapack
#XC_COMPFLAGS =

# LibXC compatibility
# Choose LibXC version: v4 (deprecated) or v5/6 (v5 and v6 have the same interface)
# Choose LibXC version: v4 (deprecated) or v5/6/7 (v5, v6 and v7 have the same interface)
#XC_LIBRARY = LibXC_v4
XC_LIBRARY = LibXC_v5
XC_LIB = -lxcf90 -lxc
#XC_LIB = -lxcf90 -lxc
XC_LIB = -lxcf03 -lxc
XC_COMPFLAGS = -I/usr/local/include

# Set FFT library
Expand Down
3 changes: 2 additions & 1 deletion src/system/system.gha.make
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@ LINKFLAGS=-fopenmp -L/usr/lib -L/usr/lib/x86_64-linux-gnu
BLAS= -llapack -lblas
# LibXC compatibility (LibXC below) or Conquest XC library
XC_LIBRARY = LibXC_v5
XC_LIB = -lxcf90 -lxc
#XC_LIB = -lxcf90 -lxc
XC_LIB = -lxcf03 -lxc
XC_COMPFLAGS = -I/usr/include
# Set FFT library
FFT_LIB=-lfftw3
Expand Down
48 changes: 24 additions & 24 deletions tools/BasisGeneration/radial_xc_LibXC_v5_module.f90
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
! Contains routines to evaluate XC energy and potential for radial charge distributions
module radial_xc

use xc_f90_lib_m
use xc_f03_lib_m

implicit none

Expand All @@ -25,8 +25,8 @@ module radial_xc
! LibXC variables
integer :: n_xc_terms
integer, dimension(2) :: i_xc_family
type(xc_f90_func_t), dimension(2) :: xc_func
type(xc_f90_func_info_t), dimension(2) :: xc_info
type(xc_f03_func_t), dimension(2) :: xc_func
type(xc_f03_func_info_t), dimension(2) :: xc_info
logical :: flag_use_libxc

contains
Expand All @@ -43,16 +43,16 @@ subroutine init_xc
integer :: vmajor, vminor, vmicro, i, j
integer, dimension(2) :: xcpart
character(len=120) :: name, kind, family, ref
type(xc_f90_func_t) :: temp_xc_func
type(xc_f90_func_info_t) :: temp_xc_info
type(xc_f03_func_t) :: temp_xc_func
type(xc_f03_func_info_t) :: temp_xc_info

! Test for LibXC or CQ
if(flag_functional_type<0) then
! --------------------------
! LibXC functional specified
! --------------------------
flag_use_libxc = .true.
call xc_f90_version(vmajor, vminor, vmicro)
call xc_f03_version(vmajor, vminor, vmicro)
if(inode==ionode.AND.iprint>0) then
if(vmajor>2) then
write(*,'("LibXC version: ",I1,".",I1,".",I1)') vmajor, vminor, vmicro
Expand All @@ -70,37 +70,37 @@ subroutine init_xc
i = floor(-flag_functional_type/1000.0_double)
! Temporary init to find exchange or correlation
if(nspin==1) then
call xc_f90_func_init(temp_xc_func, i, XC_UNPOLARIZED)
temp_xc_info = xc_f90_func_get_info(temp_xc_func)
call xc_f03_func_init(temp_xc_func, i, XC_UNPOLARIZED)
temp_xc_info = xc_f03_func_get_info(temp_xc_func)
else if(nspin==2) then
call xc_f90_func_init(temp_xc_func, i, XC_POLARIZED)
temp_xc_info = xc_f90_func_get_info(temp_xc_func)
call xc_f03_func_init(temp_xc_func, i, XC_POLARIZED)
temp_xc_info = xc_f03_func_get_info(temp_xc_func)
end if
select case(xc_f90_func_info_get_kind(temp_xc_info))
select case(xc_f03_func_info_get_kind(temp_xc_info))
case(XC_EXCHANGE)
xcpart(1) = i
xcpart(2) = -flag_functional_type - xcpart(1)*1000
case(XC_CORRELATION)
xcpart(2) = i
xcpart(1) = -flag_functional_type - xcpart(2)*1000
end select
call xc_f90_func_end(temp_xc_func)
call xc_f03_func_end(temp_xc_func)
end if
! Now initialise and output
do i=1,n_xc_terms
if(nspin==1) then
call xc_f90_func_init(xc_func(i), xcpart(i), XC_UNPOLARIZED)
xc_info(i) = xc_f90_func_get_info(xc_func(i))
call xc_f03_func_init(xc_func(i), xcpart(i), XC_UNPOLARIZED)
xc_info(i) = xc_f03_func_get_info(xc_func(i))
else if(nspin==2) then
call xc_f90_func_init(xc_func(i), xcpart(i), XC_POLARIZED)
xc_info(i) = xc_f90_func_get_info(xc_func(i))
call xc_f03_func_init(xc_func(i), xcpart(i), XC_POLARIZED)
xc_info(i) = xc_f03_func_get_info(xc_func(i))
end if
! Consistent threshold with Conquest
!if(vmajor>2) call xc_f90_func_set_dens_threshold(xc_func(i),RD_ERR)
name = xc_f90_func_info_get_name(xc_info(i))
i_xc_family(i) = xc_f90_func_info_get_family(xc_info(i))
!if(vmajor>2) call xc_f03_func_set_dens_threshold(xc_func(i),RD_ERR)
name = xc_f03_func_info_get_name(xc_info(i))
i_xc_family(i) = xc_f03_func_info_get_family(xc_info(i))
if(inode==ionode) then
select case(xc_f90_func_info_get_kind(xc_info(i)))
select case(xc_f03_func_info_get_kind(xc_info(i)))
case (XC_EXCHANGE)
write(kind, '(a)') 'an exchange functional'
case (XC_CORRELATION)
Expand Down Expand Up @@ -134,10 +134,10 @@ subroutine init_xc
" family and is defined in the reference(s):")') &
trim(name), trim(kind), trim(family)
j = 0
ref = xc_f90_func_reference_get_ref(xc_f90_func_info_get_references(xc_info(i),j))
ref = xc_f03_func_reference_get_ref(xc_f03_func_info_get_references(xc_info(i),j))
do while(j >= 0)
write(*, '(a,i1,2a)') '[', j, '] ', trim(ref)
ref = xc_f90_func_reference_get_ref(xc_f90_func_info_get_references(xc_info(i),j))
ref = xc_f03_func_reference_get_ref(xc_f03_func_info_get_references(xc_info(i),j))
end do
else
write(*,'("The functional ", a, " is ", a, ", and it belongs to the ", a, &
Expand Down Expand Up @@ -237,10 +237,10 @@ subroutine get_vxc(n_tot,rr,rho,vxc,exc)
! Call routine
select case (i_xc_family(n))
case(XC_FAMILY_LDA)
call xc_f90_lda_exc_vxc(xc_func(n),int(n_tot,kind=wide),loc_rho(1),exc_array(1),vrho(1))
call xc_f03_lda_exc_vxc(xc_func(n),int(n_tot,kind=wide),loc_rho(1),exc_array(1),vrho(1))
vxc = vxc + vrho
case(XC_FAMILY_GGA)
call xc_f90_gga_exc_vxc(xc_func(n),int(n_tot,kind=wide),loc_rho(1),sigma(1),exc_array(1),vrho(1),vsigma(1))
call xc_f03_gga_exc_vxc(xc_func(n),int(n_tot,kind=wide),loc_rho(1),sigma(1),exc_array(1),vrho(1),vsigma(1))
vxc = vxc + vrho
d2term = zero
vsigma = vsigma*two*drho_dr
Expand Down

0 comments on commit 868ab6d

Please sign in to comment.