-
Notifications
You must be signed in to change notification settings - Fork 152
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Implementation of a generic docking algorithm (#677)
* Implementation of docking algorithm Signed-off-by: cplett <[email protected]> * Update Docking Algorithm Signed-off-by: cplett <[email protected]> * Update docking algorithm for QCG use Signed-off-by: cplett <[email protected]> Signed-off-by: cplett <[email protected]>
Showing
34 changed files
with
7,297 additions
and
103 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,26 @@ | ||
# This file is part of xtb. | ||
# | ||
# Copyright (C) 2022 Sebastian Ehlert, Christoph Plett | ||
# | ||
# xtb 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. | ||
# | ||
# xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
set(dir "${CMAKE_CURRENT_SOURCE_DIR}") | ||
|
||
list(APPEND srcs | ||
"${dir}/param.f90" | ||
"${dir}/search_nci.f90" | ||
"${dir}/set_module.f90" | ||
) | ||
|
||
set(srcs ${srcs} PARENT_SCOPE) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,22 @@ | ||
# This file is part of xtb. | ||
# | ||
# Copyright (C) 2022 Sebastian Ehlert, Christoph Plett | ||
# | ||
# xtb 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. | ||
# | ||
# xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
srcs += files( | ||
'search_nci.f90', | ||
'param.f90', | ||
'set_module.f90', | ||
) |
Large diffs are not rendered by default.
Oops, something went wrong.
Large diffs are not rendered by default.
Oops, something went wrong.
Large diffs are not rendered by default.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,29 @@ | ||
# This file is part of xtb. | ||
# | ||
# Copyright (C) 2022 Sebastian Ehlert, Christoph Plett | ||
# | ||
# xtb 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. | ||
# | ||
# xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
set(dir "${CMAKE_CURRENT_SOURCE_DIR}") | ||
|
||
list(APPEND srcs | ||
"${dir}/calculator.f90" | ||
"${dir}/data.f90" | ||
"${dir}/iff_energy.f90" | ||
"${dir}/iff_ini.f90" | ||
"${dir}/iff_lmo.f90" | ||
"${dir}/iff_prepare.f90" | ||
) | ||
|
||
set(srcs ${srcs} PARENT_SCOPE) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,174 @@ | ||
! This file is part of xtb. | ||
! | ||
! Copyright (C) 2022 Stefan Grimme | ||
! | ||
! xtb 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. | ||
! | ||
! xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
!> Intermolecular force field calculator | ||
module xtb_iff_calculator | ||
use xtb_mctc_accuracy, only: wp | ||
use xtb_type_calculator, only: TCalculator | ||
use xtb_type_environment, only: TEnvironment | ||
use xtb_type_molecule, only: TMolecule, init | ||
use xtb_type_restart | ||
use xtb_iff_data, only: TIFFData | ||
use xtb_type_data, only: scc_results | ||
use xtb_iff_iffenergy, only: iff_e | ||
use xtb_docking_param | ||
use xtb_iff_iffini, only : init_iff | ||
|
||
implicit none | ||
|
||
private | ||
|
||
public :: TIFFCalculator, newIFFCalculator | ||
|
||
!> Calculator interface for xTB based methods | ||
type, extends(TCalculator) :: TIFFCalculator | ||
|
||
type(TIFFData) :: dat | ||
|
||
contains | ||
|
||
!> Perform xTB single point calculationV | ||
procedure :: singlepoint | ||
|
||
!> Write informative printout | ||
procedure :: writeInfo | ||
|
||
end type TIFFCalculator | ||
|
||
character(len=*), private, parameter :: outfmt = & | ||
'(9x,"::",1x,a,f23.12,1x,a,1x,"::")' | ||
|
||
contains | ||
|
||
subroutine newIFFCalculator(env, comb, iff_data, calc) | ||
|
||
character(len=*), parameter :: source = 'main_setup_newIFFCalculator' | ||
|
||
type(TEnvironment), intent(inout) :: env | ||
|
||
!> Combined structure of molA and molB (molA has to be first) | ||
type(TMolecule), intent(in) :: comb | ||
|
||
type(TIFFData), intent(in) :: iff_data | ||
|
||
type(TIFFCalculator), intent(out) :: calc | ||
|
||
integer, allocatable :: at(:) | ||
real(wp), allocatable :: xyz(:,:) | ||
logical :: exitRun | ||
real(wp) :: molA_e,molB_e | ||
character(len=:), allocatable :: fnam | ||
real(wp) :: icoord(6), icoord0(6) | ||
real(wp) :: rlmo2(4,(comb%n-natom_molA)*10) | ||
|
||
call set_iff_param | ||
call calc%dat%allocateIFFData(natom_molA,comb%n-natom_molA) | ||
calc%dat = iff_data | ||
|
||
xyz=calc%dat%xyz2 | ||
rlmo2=calc%dat%rlmo2 | ||
|
||
call init_iff(env,calc%dat%n1,calc%dat%n2,calc%dat%at1,calc%dat%at2,& | ||
& calc%dat%neigh,calc%dat%xyz1,calc%dat%xyz2,calc%dat%q1,& | ||
& calc%dat%q2,calc%dat%c6ab,calc%dat%z1,calc%dat%z2,& | ||
& calc%dat%cprob,calc%dat%nlmo1,calc%dat%nlmo2,calc%dat%lmo1,calc%dat%lmo2,& | ||
& calc%dat%qdr1,calc%dat%qdr2,calc%dat%rlmo1,calc%dat%rlmo2,& | ||
& calc%dat%cn1,calc%dat%cn2,calc%dat%alp1,calc%dat%alp2,calc%dat%alpab,& | ||
& calc%dat%den1,calc%dat%den2,calc%dat%gab1,calc%dat%gab2,calc%dat%qcm1,& | ||
& calc%dat%qcm2,calc%dat%n,calc%dat%at,calc%dat%xyz,calc%dat%q,icoord,icoord0,& | ||
& .false.) | ||
calc%dat%xyz2=xyz | ||
calc%dat%rlmo2=rlmo2 | ||
|
||
call env%check(exitRun) | ||
if (exitRun) then | ||
call env%error("Could not create IFF calculator", source) | ||
return | ||
end if | ||
|
||
end subroutine newIFFCalculator | ||
|
||
subroutine singlepoint(self, env, mol, chk, printlevel, restart, & | ||
& energy, gradient, sigma, hlgap, results) | ||
|
||
!> Source of the generated errors | ||
character(len=*), parameter :: source = 'iff_calculator_singlepoint' | ||
|
||
!> Calculator instance | ||
class(TIFFCalculator), intent(inout) :: self | ||
|
||
!> Computational environment | ||
type(TEnvironment), intent(inout) :: env | ||
|
||
!> Molecular structure data | ||
type(TMolecule), intent(inout) :: mol | ||
|
||
!> Wavefunction data | ||
type(TRestart), intent(inout) :: chk | ||
|
||
!> Print level for IO | ||
integer, intent(in) :: printlevel | ||
|
||
!> Restart from previous results | ||
logical, intent(in) :: restart | ||
|
||
!> Total energy | ||
real(wp), intent(out) :: energy | ||
|
||
!> Molecular gradient | ||
real(wp), intent(out) :: gradient(:, :) | ||
|
||
!> Strain derivatives | ||
real(wp), intent(out) :: sigma(:, :) | ||
|
||
!> HOMO-LUMO gab | ||
real(wp), intent(out) :: hlgap | ||
|
||
!> Detailed results | ||
type(scc_results), intent(out) :: results | ||
|
||
call iff_e(env, self%dat%n, self%dat%n1, self%dat%n2, self%dat%at1,& | ||
& self%dat%at2, self%dat%neigh, self%dat%xyz1, self%dat%xyz2,& | ||
& self%dat%q1, self%dat%q2, self%dat%c6ab, self%dat%z1, self%dat%z2,& | ||
& self%dat%nlmo1, self%dat%nlmo2, self%dat%lmo1, self%dat%lmo2,& | ||
& self%dat%rlmo1, self%dat%rlmo2,self%dat%qdr1, self%dat%qdr2,& | ||
& self%dat%cn1, self%dat%cn2, self%dat%alp1,& | ||
& self%dat%alp2, self%dat%alpab, self%dat%qct1, self%dat%qct2,& | ||
& self%dat%den1, self%dat%den2, self%dat%gab1, self%dat%gab2,& | ||
& .true., 0, energy) | ||
|
||
results%e_total=energy | ||
gradient = 0 | ||
sigma = 0 | ||
hlgap = 0 | ||
|
||
end subroutine singlepoint | ||
|
||
subroutine writeInfo(self, unit, mol) | ||
|
||
!> Calculator instance | ||
class(TIFFCalculator), intent(in) :: self | ||
|
||
!> Unit for I/O | ||
integer, intent(in) :: unit | ||
|
||
!> Molecular structure data | ||
type(TMolecule), intent(in) :: mol | ||
|
||
end subroutine writeInfo | ||
|
||
end module xtb_iff_calculator |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,191 @@ | ||
! This file is part of xtb. | ||
! | ||
! Copyright (C) 2022 Christoph Plett | ||
! | ||
! xtb 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. | ||
! | ||
! xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
!> Topological data for force field type calculations | ||
module xtb_iff_data | ||
use xtb_mctc_accuracy, only: wp | ||
use xtb_type_molecule, only: TMolecule | ||
implicit none | ||
private | ||
|
||
public :: TIFFData | ||
|
||
type :: TIFFData | ||
|
||
!> Total number of atoms | ||
integer :: n | ||
|
||
!> Number of atoms molA and B | ||
integer :: n1 | ||
integer :: n2 | ||
|
||
!> Number of LMOs molA and B | ||
integer :: nlmo1 | ||
integer :: nlmo2 | ||
|
||
!> Coordinates molA and B and whole system | ||
real(wp), allocatable :: xyz1(:, :) | ||
real(wp), allocatable :: xyz2(:, :) | ||
real(wp), allocatable :: xyz(:, :) | ||
|
||
!> LMO positions molA and B | ||
real(wp), allocatable :: rlmo1(:, :) | ||
real(wp), allocatable :: rlmo2(:, :) | ||
|
||
!> Charges | ||
real(wp), allocatable :: q1(:) | ||
real(wp), allocatable :: q2(:) | ||
real(wp), allocatable :: q(:) | ||
|
||
!> Deviation from atomic charge | ||
real(wp), allocatable :: qdr1(:) | ||
real(wp), allocatable :: qdr2(:) | ||
|
||
!> Deviation from atomic position | ||
real(wp), allocatable ::xyzdr1(:, :) | ||
real(wp), allocatable ::xyzdr2(:, :) | ||
|
||
!> Coordination numbers | ||
real(wp), allocatable :: cn1(:) | ||
real(wp), allocatable :: cn2(:) | ||
real(wp), allocatable :: cn(:) | ||
|
||
!> Electron count per element | ||
real(wp), allocatable :: z1(:) | ||
real(wp), allocatable :: z2(:) | ||
|
||
!> Polarizabilities | ||
real(wp), allocatable :: alp1(:) | ||
real(wp), allocatable :: alp2(:) | ||
real(wp), allocatable :: alpab(:, :) | ||
real(wp), allocatable :: alp0(:) | ||
|
||
!> Ordinary number | ||
integer, allocatable :: at1(:) | ||
integer, allocatable :: at2(:) | ||
integer, allocatable :: at(:) | ||
|
||
!> LMO values | ||
integer, allocatable :: lmo1(:) | ||
integer, allocatable :: lmo2(:) | ||
|
||
!> C6 coeffs for the whole system | ||
real(wp), allocatable :: c6ab(:, :) | ||
|
||
!> C6 coeffs for molA with rare gas | ||
real(wp), allocatable :: cprob(:) | ||
|
||
real(wp), allocatable :: gab1(:, :) | ||
real(wp), allocatable :: gab2(:, :) | ||
|
||
!> Frontier orbital densities | ||
real(wp), allocatable :: den1(:, :, :) | ||
real(wp), allocatable :: den2(:, :, :) | ||
|
||
!> Charge related stuff (from GFN2 calc.) | ||
real(wp), allocatable :: qcm1(:) | ||
real(wp), allocatable :: qcm2(:) | ||
real(wp), allocatable :: qct1(:, :) | ||
real(wp), allocatable :: qct2(:, :) | ||
|
||
!> Neighbour list | ||
integer, allocatable :: neigh(:, :) | ||
|
||
contains | ||
|
||
procedure :: delete | ||
procedure :: allocateIFFData | ||
|
||
end type TIFFData | ||
|
||
contains | ||
|
||
subroutine delete(self) | ||
class(TIFFData), intent(out) :: self | ||
|
||
if (allocated(self%xyz1)) deallocate (self%xyz1) | ||
if (allocated(self%rlmo1)) deallocate (self%rlmo1) | ||
if (allocated(self%q1)) deallocate (self%q1) | ||
if (allocated(self%qdr1)) deallocate (self%qdr1) | ||
if (allocated(self%xyzdr1)) deallocate (self%xyzdr1) | ||
if (allocated(self%cn1)) deallocate (self%cn1) | ||
if (allocated(self%z1)) deallocate (self%z1) | ||
if (allocated(self%alp1)) deallocate (self%alp1) | ||
if (allocated(self%qct1)) deallocate (self%qct1) | ||
if (allocated(self%at1)) deallocate (self%at1) | ||
if (allocated(self%lmo1)) deallocate (self%lmo1) | ||
if (allocated(self%xyz2)) deallocate (self%xyz2) | ||
if (allocated(self%rlmo2)) deallocate (self%rlmo2) | ||
if (allocated(self%q2)) deallocate (self%q2) | ||
if (allocated(self%qdr2)) deallocate (self%qdr2) | ||
if (allocated(self%xyzdr2)) deallocate (self%xyzdr2) | ||
if (allocated(self%cn2)) deallocate (self%cn2) | ||
if (allocated(self%z2)) deallocate (self%z2) | ||
if (allocated(self%alp2)) deallocate (self%alp2) | ||
if (allocated(self%qct2)) deallocate (self%qct2) | ||
if (allocated(self%at2)) deallocate (self%at2) | ||
if (allocated(self%lmo2)) deallocate (self%lmo2) | ||
if (allocated(self%c6ab)) deallocate (self%c6ab) | ||
if (allocated(self%alpab)) deallocate (self%alpab) | ||
if (allocated(self%cprob)) deallocate (self%cprob) | ||
if (allocated(self%xyz)) deallocate (self%xyz) | ||
if (allocated(self%q)) deallocate (self%q) | ||
if (allocated(self%cn)) deallocate (self%cn) | ||
if (allocated(self%alp0)) deallocate (self%alp0) | ||
if (allocated(self%gab1)) deallocate (self%gab1) | ||
if (allocated(self%gab2)) deallocate (self%gab2) | ||
if (allocated(self%den1)) deallocate (self%den1) | ||
if (allocated(self%den2)) deallocate (self%den2) | ||
if (allocated(self%qcm1)) deallocate (self%qcm1) | ||
if (allocated(self%qcm2)) deallocate (self%qcm2) | ||
if (allocated(self%at)) deallocate (self%at) | ||
if (allocated(self%neigh)) deallocate (self%neigh) | ||
|
||
end subroutine delete | ||
|
||
subroutine allocateIFFData(self, n1, n2) | ||
|
||
class(TIFFData), intent(out) :: self | ||
|
||
integer, intent(in) :: n1, n2 | ||
|
||
integer :: n | ||
|
||
self%n1 = n1 | ||
self%n2 = n2 | ||
|
||
!Allocate Infos of molA | ||
allocate(self%at1(n1),self%xyz1(3,n1),self%rlmo1(4,10*n1),self%q1(n1),self%lmo1(10*n1),& | ||
&self%cn1(n1),self%alp1(n1),self%qct1(n1,2),self%qdr1(n1),self%xyzdr1(3,n1),& | ||
&self%z1(n1), self%den1(2, 4, n1), self%gab1(n1, n1), self%qcm1(n1)) | ||
self%rlmo1 = 0.0_wp | ||
|
||
!Allocate Infos of molB | ||
allocate(self%at2(n2),self%xyz2(3,n2),self%rlmo2(4,10*n2),self%q2(n2),self%lmo2(10*n2),& | ||
& self%cn2(n2),self%alp2(n2),self%qct2(n2,2),self%qdr2(n2),self%xyzdr2(3,n2),& | ||
& self%z2(n2), self%den2(2, 4, n2), self%gab2(n2, n2), self%qcm2(n2)) | ||
self%rlmo2 = 0.0_wp | ||
|
||
!Allocate combined Infos | ||
self%n = n1 + n2 | ||
n = self%n | ||
allocate(self%at(n),self%xyz(3,n),self%q(n),self%c6ab(n,n),self%alp0(n),self%cn(n),self%neigh(0:n,n),& | ||
& self%alpab(n2, n1), self%cprob(n1)) | ||
|
||
end subroutine allocateIFFData | ||
|
||
end module xtb_iff_data |
Large diffs are not rendered by default.
Oops, something went wrong.
Large diffs are not rendered by default.
Oops, something went wrong.
Large diffs are not rendered by default.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,241 @@ | ||
! This file is part of xtb. | ||
! | ||
! Copyright (C) 2022 Christoph Plett | ||
! | ||
! xtb 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. | ||
! | ||
! xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
module xtb_iff_iffprepare | ||
use xtb_mctc_accuracy, only: wp | ||
use xtb_type_environment, only: TEnvironment | ||
use xtb_splitparam | ||
use xtb_iff_calculator, only: TIFFCalculator | ||
use xtb_iff_data, only: TIFFData | ||
use xtb_type_atomlist | ||
use xtb_type_molecule, only: TMolecule | ||
use xtb_setparam | ||
use xtb_type_restart, only: TRestart | ||
use xtb_type_calculator, only: TCalculator | ||
use xtb_xtb_calculator, only: TxTBCalculator | ||
use xtb_setmod, only: set_gfn | ||
use xtb_readin, only: xfind | ||
use xtb_solv_state, only: solutionState | ||
use xtb_type_data, only: scc_results | ||
use xtb_main_defaults, only: initDefaults | ||
use xtb_disp_ncoord, only: ncoord_gfn, ncoord_erf | ||
use xtb_scc_core, only: iniqshell | ||
use xtb_eeq, only: goedecker_chrgeq | ||
use xtb_main_setup, only: newCalculator | ||
use xtb_single, only: singlepoint | ||
use xtb_docking_param, only: chrg, uhf, gsolvstate_iff, pre_e_A, & | ||
& pre_e_B, optlvl, ehomo, elumo, dipol, & | ||
& natom_molA, natom_arg, split_mol | ||
|
||
implicit none | ||
|
||
private | ||
public :: prepare_IFF, precomp | ||
|
||
contains | ||
|
||
subroutine prepare_IFF(env, comb, iff_data) | ||
|
||
type(TEnvironment), intent(inout) :: env | ||
!> Combined structure of molA and molB (molA has to be first) | ||
type(TMolecule), intent(in) :: comb | ||
!> IFF data | ||
type(TIFFData) :: iff_data | ||
|
||
character(len=*), parameter :: source = 'preperation_IFFCalculator' | ||
type(TMolecule) :: molA, molB | ||
integer, allocatable :: at(:) | ||
real(wp), allocatable :: xyz(:, :) | ||
real(wp) :: molA_e, molB_e | ||
integer, allocatable :: list(:) | ||
type(TAtomList) :: atl | ||
|
||
call atl%resize(comb%n) | ||
|
||
!> First make the argument natom_arg to a list of number of atoms | ||
call atl%new(natom_arg) | ||
if (atl%get_error()) then | ||
call env%warning('something is wrong in the fixing list',source) | ||
return | ||
endif | ||
call atl%to_list(list) | ||
|
||
molA%n = size(list) | ||
natom_molA = molA%n | ||
molB%n = comb%n - molA%n | ||
|
||
if (natom_molA == 0) call env%error('No atoms of Molecule A given') | ||
if(natom_molA > comb%n) & | ||
& call env%error('More atoms of Molecule A than contained in structure') | ||
|
||
call split_mol(molA, molB, size(list), list, comb) | ||
call iff_data%allocateIFFData(molA%n, molB%n) | ||
|
||
call precomp(env, iff_data, molA, molA_e, 1) | ||
call precomp(env, iff_data, molB, molB_e, 2) | ||
|
||
end subroutine prepare_IFF | ||
|
||
subroutine precomp(env, iff_data, mol, etot, mol_num) | ||
|
||
!> Molecular structure data | ||
type(TMolecule), intent(inout) :: mol | ||
!> IFF data | ||
type(TIFFData), intent(inout) :: iff_data | ||
!> Calculation environment | ||
type(TEnvironment), intent(inout) :: env | ||
integer, intent(in) :: mol_num | ||
|
||
class(TCalculator), allocatable :: calc | ||
type(TRestart) :: chk | ||
character(len=:), allocatable :: fnv !parameter file | ||
logical :: restart = .false. | ||
real(wp) :: acc = 1.0_wp !SCF accuracy | ||
real(wp) :: egap | ||
integer :: gsolvstate !Should be gas | ||
real(wp), allocatable :: cn(:) | ||
real(wp), allocatable :: dcn(:, :, :), dq(:, :, :), g(:, :) | ||
real(wp) :: er | ||
integer, external :: ncore | ||
logical :: lgrad | ||
logical :: exist | ||
real(wp), intent(out) :: etot | ||
real(wp) :: sigma(3, 3) | ||
type(scc_results) :: res | ||
integer :: i | ||
integer :: extrun_tmp | ||
integer, allocatable :: tmp_unit | ||
logical :: newdisp_tmp | ||
integer :: itemp = 48 | ||
|
||
allocate (cn(mol%n), g(3, mol%n)) | ||
|
||
set%pr_lmo = .true. | ||
set%silent = .true. | ||
|
||
!Setting up z | ||
do i = 1, mol%n | ||
mol%z(i) = mol%at(i) - ncore(mol%at(i)) | ||
! lanthanides without f are treated as La | ||
if (mol%at(i) .gt. 57 .and. mol%at(i) .lt. 72) mol%z(i) = 3 | ||
end do | ||
|
||
!> Set GFN2 settings | ||
if (optlvl /= 'gfn1') then | ||
set%gfn_method = 2 | ||
fnv = xfind('param_gfn2-xtb.txt') | ||
extrun_tmp = set%mode_extrun | ||
set%mode_extrun = p_ext_xtb | ||
newdisp_tmp = set%newdisp | ||
set%newdisp = .true. | ||
else | ||
fnv = xfind('param_gfn1-xtb.txt') !Other stuff already set | ||
end if | ||
if (mol_num .eq. 1) then | ||
if (chrg(1) /= 0.0_wp) mol%chrg = chrg(1) | ||
if (uhf(1) /= 0.0_wp) mol%uhf = uhf(1) | ||
elseif (mol_num .eq. 2) then | ||
if (chrg(2) /= 0.0_wp) mol%chrg = chrg(2) | ||
if (uhf(2) /= 0.0_wp) mol%uhf = uhf(2) | ||
end if | ||
|
||
call open_file(itemp, 'tmp_lmo', 'w') | ||
tmp_unit = env%unit | ||
env%unit = itemp | ||
|
||
!> New calculator | ||
call newCalculator(env, mol, calc, fnv, restart, acc) | ||
call env%checkpoint("Could not setup parameterisation") | ||
|
||
! gsolvstate = solutionState%gsolv | ||
call initDefaults(env, calc, mol, gsolvstate_iff) | ||
!> initial guess, setup wavefunction | ||
select type (calc) | ||
type is (TxTBCalculator) | ||
calc%etemp = set%etemp | ||
calc%maxiter = set%maxscciter | ||
call chk%wfn%allocate(mol%n, calc%basis%nshell, calc%basis%nao) | ||
!> EN charges and CN | ||
call ncoord_gfn(mol%n, mol%at, mol%xyz, cn) | ||
if (mol%npbc > 0) then | ||
chk%wfn%q = real(set%ichrg, wp)/real(mol%n, wp) | ||
else | ||
call ncoord_erf(mol%n, mol%at, mol%xyz, cn) | ||
call goedecker_chrgeq(mol%n,mol%at,mol%xyz,real(set%ichrg,wp),cn,dcn,chk%wfn%q,dq,er,g,& | ||
.false., .false., .false.) | ||
chk%wfn%q = real(set%ichrg, wp)/real(mol%n, wp) | ||
end if | ||
!> initialize shell charges from gasteiger charges | ||
call iniqshell(calc%xtbData,mol%n,mol%at,mol%z,calc%basis%nshell,chk%wfn%q,chk%wfn%qsh,set%gfn_method) | ||
end select | ||
|
||
call delete_file('.sccnotconverged') | ||
call delete_file('charges') | ||
|
||
call env%checkpoint("Setup for calculation failed") | ||
|
||
allocate(res%iff_results) | ||
|
||
!> the SP | ||
call singlepoint & | ||
& (env, mol, chk, calc, egap, set%etemp, set%maxscciter, 2,& | ||
& exist, lgrad, acc, etot, g, sigma, res) | ||
|
||
set%pr_lmo = .false. | ||
|
||
!> Save the results | ||
if (mol_num .eq. 1) then | ||
pre_e_A = etot | ||
iff_data%n1 = res%iff_results%n | ||
iff_data%at1 = res%iff_results%at | ||
iff_data%xyz1 = res%iff_results%xyz | ||
iff_data%q1 = res%iff_results%q | ||
iff_data%nlmo1 = res%iff_results%nlmo | ||
iff_data%rlmo1 = res%iff_results%rlmo | ||
iff_data%lmo1 = res%iff_results%lmo | ||
iff_data%qct1 = res%iff_results%qct | ||
ehomo(1) = res%iff_results%ehomo | ||
elumo(1) = res%iff_results%elumo | ||
dipol(1) = res%iff_results%dipol | ||
elseif (mol_num .eq. 2) then | ||
pre_e_B = etot | ||
iff_data%n2 = res%iff_results%n | ||
iff_data%at2 = res%iff_results%at | ||
iff_data%xyz2 = res%iff_results%xyz | ||
iff_data%q2 = res%iff_results%q | ||
iff_data%nlmo2 = res%iff_results%nlmo | ||
iff_data%rlmo2 = res%iff_results%rlmo | ||
iff_data%lmo2 = res%iff_results%lmo | ||
iff_data%qct2 = res%iff_results%qct | ||
ehomo(2) = res%iff_results%ehomo | ||
elumo(2) = res%iff_results%elumo | ||
dipol(2) = res%iff_results%dipol | ||
end if | ||
|
||
if (optlvl /= 'gfn1') then | ||
set%mode_extrun = extrun_tmp | ||
set%newdisp = newdisp_tmp | ||
end if | ||
|
||
set%silent = .false. | ||
env%unit = tmp_unit | ||
call remove_file(itemp) | ||
deallocate (cn, g) | ||
|
||
end subroutine precomp | ||
|
||
end module xtb_iff_iffprepare |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,25 @@ | ||
# This file is part of xtb. | ||
# | ||
# Copyright (C) 2022 Sebastian Ehlert, Christoph Plett | ||
# | ||
# xtb 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. | ||
# | ||
# xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
srcs += files( | ||
'calculator.f90', | ||
'data.f90', | ||
'iff_energy.f90', | ||
'iff_ini.f90', | ||
'iff_lmo.f90', | ||
'iff_prepare.f90', | ||
) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Large diffs are not rendered by default.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -17,6 +17,7 @@ | |
|
||
prog += files( | ||
'argparser.f90', | ||
'dock.f90', | ||
'info.f90', | ||
'main.F90', | ||
'primary.f90', | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,176 @@ | ||
! This file is part of xtb. | ||
! SPDX-Identifier: LGPL-3.0-or-later | ||
! | ||
! xtb 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. | ||
! | ||
! xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
module test_docking | ||
use testdrive, only : new_unittest, unittest_type, error_type, check_ => check, test_failed | ||
implicit none | ||
private | ||
|
||
public :: collect_docking | ||
|
||
contains | ||
|
||
!> Collect all exported unit tests | ||
subroutine collect_docking(testsuite) | ||
!> Collection of tests | ||
type(unittest_type), allocatable, intent(out) :: testsuite(:) | ||
|
||
testsuite = [ & | ||
new_unittest("eth_wat", test_dock_eth_wat)]!, & | ||
! new_unittest("ellips", test_iff_ellips), & | ||
! ] | ||
|
||
end subroutine collect_docking | ||
|
||
|
||
subroutine test_dock_eth_wat(error) | ||
use xtb_type_environment, only: TEnvironment, init | ||
use xtb_mctc_accuracy, only: wp | ||
use xtb_type_environment, only: TEnvironment | ||
use xtb_type_molecule | ||
use xtb_setparam, only: initrand | ||
use xtb_mctc_systools | ||
use xtb_setmod | ||
use xtb_docking_set_module | ||
use xtb_docking_param | ||
use xtb_iff_iffini, only: init_iff | ||
use xtb_iff_iffprepare, only: precomp | ||
use xtb_iff_iffenergy | ||
use xtb_docking_search_nci, only: docking_search | ||
use xtb_mctc_systools | ||
use xtb_iff_data, only: TIFFData | ||
type(error_type), allocatable, intent(out) :: error | ||
!> All important variables stored here | ||
type(TIFFData) :: iff_data | ||
real(wp),parameter :: thr = 1.0e-6_wp | ||
real(wp) :: icoord0(6),icoord(6) | ||
integer :: n1 | ||
integer :: at1(9) | ||
real(wp) :: xyz1(3,9) | ||
integer :: n2 | ||
integer :: at2(3) | ||
real(wp) :: xyz2(3,3) | ||
integer,parameter :: n = 12 | ||
integer :: at(n) | ||
real(wp) :: xyz(3,n) | ||
real(wp) :: molA_e, molB_e | ||
|
||
logical, parameter :: restart = .false. | ||
|
||
type(TMolecule) :: molA,molB,comb | ||
real(wp) :: r(3),e | ||
integer :: i, j, k | ||
type(TEnvironment) :: env | ||
character(len=:), allocatable :: fnam | ||
|
||
logical :: exist | ||
|
||
n1 = 9 | ||
at1 = [6,6,1,1,1,1,8,1,1] | ||
xyz1 = reshape(& | ||
&[-10.23731657240310_wp, 4.49526140160057_wp,-0.01444418438295_wp, & | ||
& -8.92346521409264_wp, 1.93070071439448_wp,-0.06395255870166_wp, & | ||
& -11.68223026601517_wp, 4.59275319594179_wp,-1.47773402464476_wp, & | ||
& -8.87186386250594_wp, 5.99323351202269_wp,-0.34218865473603_wp, & | ||
& -11.13173905821587_wp, 4.79659470137971_wp, 1.81087156124027_wp, & | ||
& -8.00237319881732_wp, 1.64827398274591_wp,-1.90766384850460_wp, & | ||
& -10.57950417459641_wp,-0.08678859323640_wp, 0.45375344239209_wp, & | ||
& -7.47634978432660_wp, 1.83563324786661_wp, 1.40507877109963_wp, & | ||
& -11.96440476139715_wp,-0.02296384600667_wp,-0.72783557254661_wp],& | ||
& shape(xyz1)) | ||
|
||
n2 = 3 | ||
at2 = [8,1,1] | ||
xyz2 = reshape(& | ||
&[-14.55824225787638_wp, 0.85763330814882_wp, 0.00000000000000_wp, & | ||
& -12.72520790897730_wp, 0.85763330814882_wp, 0.00000000000000_wp, & | ||
& -15.16924740842229_wp,-0.86379381534203_wp,-0.15285994688912_wp],& | ||
& shape(xyz2)) | ||
|
||
call init(env) | ||
call init(molA, at1, xyz1) | ||
call init(molB, at2, xyz2) | ||
call iff_data%allocateIFFData(molA%n, molB%n) | ||
|
||
call initrand | ||
|
||
call set_iff_param | ||
fnam = 'xtblmoinfo' | ||
set%pr_local = .false. | ||
|
||
call precomp(env, iff_data, molA, molA_e, 1) | ||
call check_(error, molA_e,-11.3943358674_wp, thr=thr) | ||
call precomp(env, iff_data, molB, molB_e, 2) | ||
|
||
call env%checkpoint("LMO computation failed") | ||
|
||
call cmadock(molA%n, molA%n, molA%at, molA%xyz, r) | ||
do i = 1, 3 | ||
molA%xyz(i, 1:molA%n) = molA%xyz(i, 1:molA%n) - r(i) | ||
end do | ||
call cmadock(molB%n, molB%n, molB%at, molB%xyz, r) | ||
do i = 1, 3 | ||
molB%xyz(i, 1:molB%n) = molB%xyz(i, 1:molB%n) - r(i) | ||
end do | ||
|
||
call init_iff(env, iff_data%n1, iff_data%n2, iff_data%at1, iff_data%at2,& | ||
& iff_data%neigh, iff_data%xyz1, iff_data%xyz2, iff_data%q1, & | ||
& iff_data%q2, iff_data%c6ab, iff_data%z1, iff_data%z2,& | ||
& iff_data%cprob, iff_data%nlmo1, iff_data%nlmo2, iff_data%lmo1, iff_data%lmo2,& | ||
& iff_data%qdr1, iff_data%qdr2, iff_data%rlmo1, iff_data%rlmo2,& | ||
& iff_data%cn1, iff_data%cn2, iff_data%alp1, iff_data%alp2, iff_data%alpab,& | ||
& iff_data%den1, iff_data%den2, iff_data%gab1, iff_data%gab2, iff_data%qcm1,& | ||
& iff_data%qcm2, iff_data%n, iff_data%at, iff_data%xyz, iff_data%q, icoord, icoord0,& | ||
& .false.) | ||
|
||
call check_(error, icoord(1) ,-4.5265_wp, thr=1.0e-3_wp) | ||
|
||
call env%checkpoint("Initializing xtb-IFF failed.") | ||
|
||
call iff_e(env, iff_data%n, iff_data%n1, iff_data%n2, iff_data%at1, iff_data%at2,& | ||
& iff_data%neigh, iff_data%xyz1, iff_data%xyz2, iff_data%q1, iff_data%q2,& | ||
& iff_data%c6ab, iff_data%z1, iff_data%z2,& | ||
& iff_data%nlmo1, iff_data%nlmo2, iff_data%lmo1, iff_data%lmo2, & | ||
& iff_data%rlmo1, iff_data%rlmo2,& | ||
& iff_data%qdr1, iff_data%qdr2, iff_data%cn1, iff_data%cn2, iff_data%alp1, & | ||
& iff_data%alp2, iff_data%alpab, iff_data%qct1, iff_data%qct2, & | ||
& iff_data%den1, iff_data%den2, iff_data%gab1, iff_data%gab2, & | ||
& set%verbose, 0, e, icoord) | ||
|
||
call check_(error, e,0.07745330953243718_wp, thr=thr) | ||
|
||
call env%checkpoint("xtb-IFF sp computation failed") | ||
|
||
call set_optlvl(env) !Sets the optimization level for search in global parameters | ||
! call docking_search(env, molA, molB, n, n1, n2, at1, at2, neigh, xyz1,& | ||
! & xyz2, q1, q2, c6ab, z1, z2,& | ||
! &nlmo1, nlmo2, lmo1, lmo2, rlmo1, rlmo2,& | ||
! &qdr1, qdr2, cn1, cn2, alp1, alp2, alpab, qct1, qct2,& | ||
! &den1, den2, gab1, gab2, molA_e, molB_e,& | ||
! &cprob, e, icoord, comb) | ||
|
||
! call env%checkpoint("Docking algorithm failed") | ||
|
||
! call check_(error, calc%topo%nbond,6) | ||
! | ||
! call check_(error, res_gff%e_total,-0.76480130317838_wp, thr=thr) | ||
|
||
call molA%deallocate | ||
call molB%deallocate | ||
|
||
end subroutine test_dock_eth_wat | ||
|
||
end module test_docking |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,101 @@ | ||
! This file is part of xtb. | ||
! SPDX-Identifier: LGPL-3.0-or-later | ||
! | ||
! xtb 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. | ||
! | ||
! xtb 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 xtb. If not, see <https://www.gnu.org/licenses/>. | ||
|
||
module test_iff | ||
use testdrive, only : new_unittest, unittest_type, error_type, check_ => check, test_failed | ||
implicit none | ||
private | ||
|
||
public :: collect_iff | ||
|
||
contains | ||
|
||
!> Collect all exported unit tests | ||
subroutine collect_iff(testsuite) | ||
!> Collection of tests | ||
type(unittest_type), allocatable, intent(out) :: testsuite(:) | ||
|
||
testsuite = [ & | ||
new_unittest("iff_sp", test_iff_sp) & | ||
] | ||
|
||
end subroutine collect_iff | ||
|
||
|
||
subroutine test_iff_sp(error) | ||
use xtb_mctc_accuracy, only : wp | ||
use xtb_mctc_systools | ||
use xtb_type_environment | ||
use xtb_type_options | ||
use xtb_type_molecule | ||
use xtb_type_data | ||
use xtb_setparam | ||
use xtb_setmod | ||
use xtb_docking_param | ||
use xtb_type_restart, only: TRestart | ||
use xtb_iff_calculator, only : TIFFCalculator, newIFFCalculator | ||
use xtb_iff_data, only : TIFFData | ||
use xtb_iff_iffprepare, only : prepare_IFF | ||
type(error_type), allocatable, intent(out) :: error | ||
real(wp),parameter :: thr = 1.0e-10_wp | ||
integer, parameter :: nat = 6 | ||
integer, parameter :: at(nat) = [8,1,1,8,1,1] | ||
real(wp),parameter :: xyz(3,nat) = reshape(& | ||
&[-0.04394313126682_wp,-0.15162589575685_wp,-0.12104386666899_wp, & | ||
& 1.57021196791551_wp, 0.39852223676357_wp,-0.74238980424452_wp, & | ||
& -0.52096572705612_wp,-1.61453119575215_wp,-1.08142949421996_wp, & | ||
& -3.35527313086215_wp, 3.63311912367937_wp,-1.97688072772302_wp, & | ||
& -4.33218397586988_wp, 4.42399249914350_wp,-0.67195282333972_wp, & | ||
& -2.30284007732108_wp, 2.38679302539156_wp,-1.14422985849389_wp],& | ||
& shape(xyz)) | ||
|
||
type(TMolecule) :: mol | ||
type(TEnvironment) :: env | ||
type(TIFFCalculator) :: calc | ||
type(TIFFData) :: iff_data | ||
|
||
real(wp) :: etot,egap | ||
real(wp), allocatable :: g(:,:) | ||
type(TRestart) :: chk | ||
real(wp) :: sigma(3,3) | ||
type(scc_results) :: res | ||
|
||
|
||
logical :: exist | ||
|
||
call init(env) | ||
call init(mol,at,xyz) | ||
|
||
natom_arg = '1-3' | ||
call prepare_IFF(env, mol, iff_data) | ||
call env%checkpoint("Could not generate electronic properties for IFF") | ||
|
||
call newIFFCalculator(env, mol, iff_data, calc) | ||
|
||
call env%checkpoint("xtb-IFF parameter setup failed") | ||
|
||
allocate( g(3,mol%n), source = 0.0_wp ) | ||
|
||
call calc%singlepoint(env, mol, chk, 2, exist, etot, g, sigma, egap, res) | ||
write(*,*) 'WW', etot | ||
|
||
call check_(error, etot,-0.002628051951328639_wp, thr=thr) | ||
|
||
call mol%deallocate | ||
|
||
end subroutine test_iff_sp | ||
|
||
end module test_iff |