Skip to content

Commit

Permalink
Consistently change all old XHCFF statments to the new libpvol
Browse files Browse the repository at this point in the history
  • Loading branch information
pprcht committed Jan 24, 2025
1 parent f25a4f7 commit 909bdb6
Show file tree
Hide file tree
Showing 13 changed files with 180 additions and 166 deletions.
4 changes: 2 additions & 2 deletions .gitmodules
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,6 @@
path = subprojects/tblite
url = https://github.com/pprcht/tblite.git
branch = xtb_solvation
[submodule "subprojects/libpvol"]
path = subprojects/libpvol
[submodule "subprojects/pvol"]
path = subprojects/pvol
url = https://github.com/neudecker-group/libpvol.git
8 changes: 4 additions & 4 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ if(NOT TARGET "gfn0::gfn0" AND WITH_GFN0)
endif()

# libpvol
if(NOT TARGET "libpvol::libpvol" AND WITH_LIBPVOL)
if(NOT TARGET "pvol::pvol" AND WITH_LIBPVOL)
find_package("libpvol" REQUIRED)
add_compile_definitions(WITH_LIBPVOL)
endif()
Expand Down Expand Up @@ -150,7 +150,7 @@ if(WITH_OBJECT AND NOT STATICBUILD)
$<$<BOOL:${WITH_TBLITE}>:tblite::tblite>
$<$<BOOL:${WITH_GFN0}>:gfn0::gfn0>
$<$<BOOL:${WITH_GFNFF}>:gfnff::gfnff>
$<$<BOOL:${WITH_XHCFF}>:xhcff::xhcff>
$<$<BOOL:${WITH_LIBPVOL}>:pvol::pvol>
$<$<BOOL:${WITH_TOMLF}>:toml-f::toml-f>
$<$<BOOL:${WITH_LWONIOM}>:lwoniom::lwoniom>
$<$<BOOL:${WITH_OpenMP}>:OpenMP::OpenMP_Fortran>
Expand Down Expand Up @@ -201,7 +201,7 @@ target_link_libraries(
$<$<BOOL:${WITH_TBLITE}>:tblite::tblite>
$<$<BOOL:${WITH_GFN0}>:gfn0::gfn0>
$<$<BOOL:${WITH_GFNFF}>:gfnff::gfnff>
$<$<BOOL:${WITH_XHCFF}>:xhcff::xhcff>
$<$<BOOL:${WITH_LIBPVOL}>:pvol::pvol>
$<$<BOOL:${WITH_TOMLF}>:toml-f::toml-f>
$<$<BOOL:${WITH_LWONIOM}>:lwoniom::lwoniom>
$<$<BOOL:${STATICBUILD}>:-static>
Expand Down Expand Up @@ -246,7 +246,7 @@ if (WITH_OBJECT AND NOT STATICBUILD)
$<$<BOOL:${WITH_TBLITE}>:tblite::tblite>
$<$<BOOL:${WITH_GFN0}>:gfn0::gfn0>
$<$<BOOL:${WITH_GFNFF}>:gfnff::gfnff>
$<$<BOOL:${WITH_XHCFF}>:xhcff::xhcff>
$<$<BOOL:${WITH_LIBPVOL}>:pvol::pvol>
$<$<BOOL:${WITH_TOMLF}>:toml-f::toml-f>
$<$<BOOL:${WITH_LWONIOM}>:lwoniom::lwoniom>
)
Expand Down
6 changes: 3 additions & 3 deletions config/modules/Findlibpvol.cmake
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,8 @@
# You should have received a copy of the GNU Lesser General Public License
# along with crest. If not, see <https://www.gnu.org/licenses/>.

set(_lib "libpvol")
set(_pkg "LIBPVOL")
set(_lib "pvol")
set(_pkg "PVOL")
set(_url "https://github.com/neudecker-group/libpvol.git")

if(NOT DEFINED "${_pkg}_FIND_METHOD")
Expand All @@ -27,7 +27,7 @@ include("${CMAKE_CURRENT_LIST_DIR}/crest-utils.cmake")
crest_find_package("${_lib}" "${${_pkg}_FIND_METHOD}" "${_url}")

set(found FALSE)
if(TARGET "libpvol::libpvol")
if(TARGET "pvol::pvol")
set (found TRUE)
endif()
message(STATUS "Found libpvol: ${found}")
Expand Down
2 changes: 1 addition & 1 deletion src/calculator/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ list(APPEND srcs
"${dir}/api_helpers.F90"
"${dir}/api_engrad.f90"
"${dir}/gradreader.f90"
"${dir}/xhcff.F90"
"${dir}/libpvol.F90"
"${dir}/subprocess_types.f90"
"${dir}/xtb_sc.f90"
"${dir}/orca_sc.f90"
Expand Down
22 changes: 11 additions & 11 deletions src/calculator/api_engrad.f90
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ module api_engrad
use tblite_api
use gfn0_api
use gfnff_api
use xhcff_api
use libpvol_api
use lj
implicit none
!>--- private module variables and parameters
Expand All @@ -42,7 +42,7 @@ module api_engrad
public :: tblite_engrad
public :: gfn0_engrad,gfn0occ_engrad
public :: gfnff_engrad
public :: xhcff_engrad
public :: libpvol_engrad
public :: lj_engrad !> RE-EXPORT

!=========================================================================================!
Expand Down Expand Up @@ -280,7 +280,7 @@ end subroutine gfnff_engrad

!========================================================================================!

subroutine xhcff_engrad(mol,calc,energy,grad,iostatus)
subroutine libpvol_engrad(mol,calc,energy,grad,iostatus)
!***************************************************************
!* Interface singlepoint call between CREST and XHC force field
!***************************************************************
Expand All @@ -300,33 +300,33 @@ subroutine xhcff_engrad(mol,calc,energy,grad,iostatus)
pr = .false.
!>--- setup system call information
!$omp critical
call xhcff_initcheck(calc,loadnew)
call libpvol_initcheck(calc,loadnew)
!>--- printout handling
call api_handle_output(calc,'xhcff.out',mol,pr)
call api_handle_output(calc,'libpvol.out',mol,pr)
!>--- populate parameters
if (loadnew) then
!> call xhcff with verbosity turned off
call xhcff_setup(mol,calc%xhcff,calc%extpressure,calc%ngrid,calc%proberad, &
& calc%vdwset,pr,calc%prch,iostatus)
!> call libpvol with verbosity turned off
call libpvol_setup(mol,calc%libpvol,calc%extpressure,calc%pvmodel, &
& calc%ngrid,calc%proberad,calc%vdwset,calc%pvradscal,pr,calc%prch,iostatus)
end if
!$omp end critical
if (iostatus /= 0) return

!>--- do the engrad call
call initsignal()
call xhcff_sp(mol,calc%xhcff,energy,grad,iostatus)
call libpvol_sp(mol,calc%libpvol,energy,grad,iostatus)
if (iostatus /= 0) return

!>--- printout
if (pr) then
!> the xhcff_sp call includes the printout within xhcff-lib
!> the libpvol_sp call includes the printout within libpvol-lib
call api_print_e_grd(pr,calc%prch,mol,energy,grad)
end if

!>--- postprocessing, getting other data

return
end subroutine xhcff_engrad
end subroutine libpvol_engrad

!========================================================================================!
!========================================================================================!
Expand Down
12 changes: 6 additions & 6 deletions src/calculator/api_helpers.F90
Original file line number Diff line number Diff line change
Expand Up @@ -372,20 +372,20 @@ end subroutine gfnff_properties

!========================================================================================!

!>--- XHCFF setup/helper routines
subroutine xhcff_initcheck(calc,loadnew)
!>--- LIBPVOL setup/helper routines
subroutine libpvol_initcheck(calc,loadnew)
implicit none
type(calculation_settings),intent(inout) :: calc
logical,intent(out) :: loadnew
loadnew = .false.
#ifdef WITH_XHCFF
if (.not.allocated(calc%xhcff)) then
allocate (calc%xhcff)
#ifdef WITH_LIBPVOL
if (.not.allocated(calc%libpvol)) then
allocate (calc%libpvol)
loadnew = .true.
end if
if (calc%apiclean) loadnew = .true.
#endif
end subroutine xhcff_initcheck
end subroutine libpvol_initcheck

!========================================================================================!
!========================================================================================!
Expand Down
28 changes: 15 additions & 13 deletions src/calculator/calc_type.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module calc_type
use tblite_api
use gfn0_api
use gfnff_api,only:gfnff_data
use xhcff_api,only:xhcff_calculator
use libpvol_api,only:libpvol_calculator
!>--- other types
use orca_type
use lwoniom_module
Expand All @@ -47,7 +47,7 @@ module calc_type
integer :: gfn0 = 7
integer :: gfn0occ = 8
integer :: gfnff = 9
integer :: xhcff = 10
integer :: libpvol = 10
integer :: lj = 11
end type enum_jobtype
type(enum_jobtype), parameter,public :: jobtype = enum_jobtype()
Expand All @@ -63,7 +63,7 @@ module calc_type
& 'GFN0-xTB calculation via GFN0 lib ', &
& 'GFN0*-xTB calculation via GFN0 lib ', &
& 'GFN-FF calculation via GFNFF lib ', &
& 'XHCFF calculation via XHCFF-lib ', &
& 'external pressure calculation via libpvol ', &
& 'Lennard-Jones potential calculation ' ]
!&>

Expand Down Expand Up @@ -158,12 +158,14 @@ module calc_type
!>--- GFN-FF data
type(gfnff_data),allocatable :: ff_dat

!>--- XHCFF data
integer :: ngrid = 230 !> lebedev grid points per atom
real(wp) :: extpressure = 0.0_wp !> hydorstatic pressure in Gpa
real(wp) :: proberad = 1.5_wp !> proberadius in Angstroem
integer :: vdwset = 0 !> Set of VDW radii to use in sas calculation -> default D3, 1 -> Bondi
type(xhcff_calculator),allocatable :: xhcff
!>--- libpvol data
integer :: pvmodel = 1 !> libpvol model type (0=XHCFF, 1=PV)
integer :: ngrid = 230 !> lebedev grid points per atom
real(wp) :: extpressure = 0.0_wp !> hydorstatic pressure in Gpa
real(wp) :: proberad = 1.5_wp !> proberadius in Angstroem
integer :: vdwset = 0 !> Type of VDW radii -> 0 (default) D3, 1 -> Bondi
real(wp) :: pvradscal = 1.0_wp !> Scaling factor for SAS radii
type(libpvol_calculator),allocatable :: libpvol

!> ONIOM fragment IDs
integer :: ONIOM_highlowroot = 0
Expand Down Expand Up @@ -352,7 +354,7 @@ subroutine calculation_deallocate_params(self)
if(allocated(self%calcs(i)%tblite)) deallocate(self%calcs(i)%tblite)
if(allocated(self%calcs(i)%g0calc)) deallocate(self%calcs(i)%g0calc)
if(allocated(self%calcs(i)%ff_dat)) deallocate(self%calcs(i)%ff_dat)
if(allocated(self%calcs(i)%xhcff)) deallocate(self%calcs(i)%xhcff)
if(allocated(self%calcs(i)%libpvol)) deallocate(self%calcs(i)%libpvol)
end do
end if
end subroutine calculation_deallocate_params
Expand Down Expand Up @@ -913,7 +915,7 @@ subroutine calculation_settings_deallocate(self)
if (allocated(self%tblite)) deallocate (self%tblite)
if (allocated(self%g0calc)) deallocate (self%g0calc)
if (allocated(self%ff_dat)) deallocate (self%ff_dat)
if (allocated(self%xhcff)) deallocate (self%xhcff)
if (allocated(self%libpvol)) deallocate (self%libpvol)

self%id = 0
self%prch = stdout
Expand Down Expand Up @@ -1039,8 +1041,8 @@ subroutine calculation_settings_shortflag(self)
self%shortflag = 'GFN0-xTB*'
case( jobtype%gfnff )
self%shortflag = 'GFN-FF'
case( jobtype%xhcff )
self%shortflag = 'XHCFF'
case( jobtype%libpvol )
self%shortflag = 'LIVPVOL'
case( jobtype%lj )
self%shortflag = 'LJ'
case default
Expand Down
6 changes: 3 additions & 3 deletions src/calculator/calculator.F90
Original file line number Diff line number Diff line change
Expand Up @@ -351,9 +351,9 @@ subroutine potential_core(molptr,calc,id,iostatus)
!> GFN-FF api
call gfnff_engrad(molptr,calc%calcs(id),calc%etmp(id),calc%grdtmp(:,1:pnat,id),iostatus)

case (jobtype%xhcff)
!> XHCFF-lib
call xhcff_engrad(molptr,calc%calcs(id),calc%etmp(id),calc%grdtmp(:,1:pnat,id),iostatus)
case (jobtype%libpvol)
!> libpvol
call libpvol_engrad(molptr,calc%calcs(id),calc%etmp(id),calc%grdtmp(:,1:pnat,id),iostatus)

case (jobtype%turbomole)
!> Turbomole-style SPs
Expand Down
132 changes: 132 additions & 0 deletions src/calculator/libpvol.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,132 @@
!================================================================================!
! This file is part of crest.
!
! Copyright (C) 2023 Philipp Pracht
!
! crest is free software: you can redistribute it and/or modify it under
! the terms of the GNU Lesser General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! crest is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU Lesser General Public License for more details.
!
! You should have received a copy of the GNU Lesser General Public License
! along with crest. If not, see <https://www.gnu.org/licenses/>.
!================================================================================!

module libpvol_api
use iso_fortran_env,only:wp => real64,stdout => output_unit
use strucrd
#ifdef WITH_LIBPVOL
use libpvol_interface
#endif
implicit none
private

#ifndef WITH_LIBPVOL
!> this is a placeholder if no libpvol module is used!
type :: libpvol_calculator
integer :: id = 0
end type libpvol_calculator
#endif

public :: libpvol_calculator !> if compiled without(!!!) -DWITH_LIBPVOL=true this will export
!> the placeholder from above. Otherwise it will re-export
!> the type from libpvol_interface

public :: libpvol_setup,libpvol_sp,libpvol_print

!========================================================================================!
!========================================================================================!
contains !>--- Module routines start here
!========================================================================================!
!========================================================================================!

subroutine libpvol_setup(mol, libpvol, pressure, model, gridpts, &
& proberad, vdwset, radscal, pr, iunit, iostatus)
implicit none
type(coord),intent(in) :: mol
real(wp), intent(in) :: pressure !> pressure
integer,intent(in) :: model
integer, intent(in) :: gridpts
real(wp), intent(in) :: proberad
integer, intent(in) :: vdwset
real(wp),intent(in) :: radscal
type(libpvol_calculator),intent(inout) :: libpvol
integer, intent(inout) :: iostatus
logical, intent(in) :: pr
integer,intent(in) :: iunit
#ifdef WITH_LIBPVOL
!> initialize LIBPVOL
select case(model)
case (1) !> PV
call libpvol%init(mol%nat,mol%at,mol%xyz,pressure,'PV', &
& gridpts=gridpts, proberad=proberad, verbose=pr,iunit=iunit, &
& printlevel=2,scaling=radscal,vdwset=vdwset,iostat=iostatus)
case (0) !> XHCFF
call libpvol%init(mol%nat,mol%at,mol%xyz,pressure,'XHCFF', &
& gridpts=gridpts, proberad=proberad, verbose=pr,iunit=iunit, &
& printlevel=2,scaling=radscal,vdwset=vdwset,iostat=iostatus)
case default
error stop 'Unkown libpvol model type'
end select

#else /* WITH_LIBPVOL */
write (stdout,*) 'Error: Compiled without LIBPVOL-lib support!'
write (stdout,*) 'Use -DWITH_LIBPVOL=true in the setup to enable this function'
error stop
#endif
end subroutine libpvol_setup

!========================================================================================!

subroutine libpvol_sp(mol,libpvol,energy,gradient,iostatus)
!********************************************************
!* The actual energy+gradient call to libpvol-lib.
!* Requires the libpvol_calculator object to be set up already.
!* Note that the original libpvol has no contribution to
!* the energy, only to the gradient
!********************************************************
implicit none
!> INPUT
type(coord),intent(in) :: mol
type(libpvol_calculator),intent(inout) :: libpvol
!> OUTPUT
real(wp),intent(out) :: energy
real(wp),intent(out) :: gradient(3,mol%nat)
integer,intent(out) :: iostatus
!> LOCAL
logical :: fail
energy = 0.0_wp
gradient = 0.0_wp
iostatus = 0
fail = .false.
#ifdef WITH_LIBPVOL
!TODO update
call libpvol%singlepoint(mol%nat,mol%at,mol%xyz,energy,gradient,iostat=iostatus)
#else
write (stdout,*) 'Error: Compiled without LIBPVOL-lib support!'
write (stdout,*) 'Use -DWITH_LIBPVOL=true in the setup to enable this function'
error stop
#endif
end subroutine libpvol_sp

!========================================================================================!

subroutine libpvol_print(iunit,libpvol)
implicit none
integer,intent(in) :: iunit
type(libpvol_calculator),intent(in) :: libpvol
#ifdef WITH_LIBPVOL
call libpvol%info(iunit)
#endif
return
end subroutine libpvol_print

!========================================================================================!
!========================================================================================!
end module libpvol_api

Loading

0 comments on commit 909bdb6

Please sign in to comment.