Skip to content

Commit

Permalink
Modify test and add cutoff via interface
Browse files Browse the repository at this point in the history
  • Loading branch information
thfroitzheim committed Nov 11, 2024
1 parent dfad126 commit 1318341
Show file tree
Hide file tree
Showing 2 changed files with 69 additions and 28 deletions.
20 changes: 12 additions & 8 deletions src/mctc/ncoord.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,15 +36,17 @@ module mctc_ncoord
contains

!> Create a new generic coordination number container
subroutine new_ncoord(self, mol, cn_type, kcn, rcov, en)
subroutine new_ncoord(self, mol, cn_type, kcn, cutoff, rcov, en)
!> Instance of the coordination number container
class(ncoord_type), allocatable, intent(out) :: self
!> Molecular structure data
type(structure_type), intent(in) :: mol
!> Coordination number type
character(len=*), intent(in) :: cn_type
!> Steepness of counting function
real(wp), optional :: kcn
!> Optional steepness of counting function
real(wp), intent(in), optional :: kcn
!> Optional real space cutoff
real(wp), intent(in), optional :: cutoff
!> Optional set of covalent radii to be used in CN
real(wp), intent(in), optional :: rcov(:)
!> Optional set of electronegativity to be use din CN
Expand All @@ -56,35 +58,37 @@ subroutine new_ncoord(self, mol, cn_type, kcn, rcov, en)
block
type(exp_ncoord_type), allocatable :: tmp
allocate(tmp)
call new_exp_ncoord(tmp, mol, kcn=kcn, rcov=rcov)
call new_exp_ncoord(tmp, mol, kcn=kcn, cutoff=cutoff, rcov=rcov)
call move_alloc(tmp, self)
end block
case("dexp")
block
type(dexp_ncoord_type), allocatable :: tmp
allocate(tmp)
call new_dexp_ncoord(tmp, mol, rcov=rcov)
call new_dexp_ncoord(tmp, mol, cutoff=cutoff, rcov=rcov)
call move_alloc(tmp, self)
end block
case("erf")
block
type(erf_ncoord_type), allocatable :: tmp
allocate(tmp)
call new_erf_ncoord(tmp, mol, kcn=kcn, rcov=rcov)
call new_erf_ncoord(tmp, mol, kcn=kcn, cutoff=cutoff, rcov=rcov)
call move_alloc(tmp, self)
end block
case("erf_en")
block
type(erf_en_ncoord_type), allocatable :: tmp
allocate(tmp)
call new_erf_en_ncoord(tmp, mol, kcn=kcn, rcov=rcov, en=en)
call new_erf_en_ncoord(tmp, mol, kcn=kcn, cutoff=cutoff, &
& rcov=rcov, en=en)
call move_alloc(tmp, self)
end block
case("dftd4")
block
type(erf_dftd4_ncoord_type), allocatable :: tmp
allocate(tmp)
call new_erf_dftd4_ncoord(tmp, mol, kcn=kcn, rcov=rcov, en=en)
call new_erf_dftd4_ncoord(tmp, mol, kcn=kcn, cutoff=cutoff, &
& rcov=rcov, en=en)
call move_alloc(tmp, self)
end block
end select
Expand Down
77 changes: 57 additions & 20 deletions test/test_ncoord.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module test_ncoord
use mctc_ncoord_erf_en, only : erf_en_ncoord_type, new_erf_en_ncoord
use mctc_ncoord_erf_dftd4, only : erf_dftd4_ncoord_type, new_erf_dftd4_ncoord
use mctc_ncoord_type
use mctc_ncoord, only : new_ncoord
implicit none
private

Expand Down Expand Up @@ -243,8 +244,9 @@ subroutine test_cn_mb01_dexp(error)
type(error_type), allocatable, intent(out) :: error

type(structure_type) :: mol
type(dexp_ncoord_type) :: dexp_ncoord
class(ncoord_type), allocatable :: dexp_ncoord
real(wp), allocatable :: rcov(:)
real(wp), allocatable :: cn(:)

real(wp), parameter :: cutoff = 30.0_wp
real(wp), parameter :: ref(16) = [&
Expand All @@ -257,11 +259,16 @@ subroutine test_cn_mb01_dexp(error)

call get_structure(mol, "mindless01")

allocate(rcov(mol%nid))
allocate(rcov(mol%nid), cn(mol%nat))
rcov(:) = get_covalent_rad(mol%num)
! Test also the external interface
call new_ncoord(dexp_ncoord, mol, "dexp", cutoff=cutoff, rcov=rcov)
call dexp_ncoord%get_cn(mol, cn)

call new_dexp_ncoord(dexp_ncoord, mol, cutoff=cutoff, rcov=rcov)
call test_cn_gen(error, mol, dexp_ncoord, cutoff, ref)
if (any(abs(cn - ref) > thr)) then
call test_failed(error, "Coordination numbers do not match")
print'(3es21.14)', cn

Check warning on line 270 in test/test_ncoord.f90

View check run for this annotation

Codecov / codecov/patch

test/test_ncoord.f90#L270

Added line #L270 was not covered by tests
end if

end subroutine test_cn_mb01_dexp

Expand Down Expand Up @@ -499,8 +506,9 @@ subroutine test_cn_mb01_exp(error)
type(error_type), allocatable, intent(out) :: error

type(structure_type) :: mol
type(exp_ncoord_type) :: exp_ncoord
class(ncoord_type), allocatable :: exp_ncoord
real(wp), allocatable :: rcov(:)
real(wp), allocatable :: cn(:)

real(wp), parameter :: cutoff = 30.0_wp
real(wp), parameter :: ref(16) = [&
Expand All @@ -513,12 +521,18 @@ subroutine test_cn_mb01_exp(error)

call get_structure(mol, "mindless01")

allocate(rcov(mol%nid))
allocate(rcov(mol%nid), cn(mol%nat))
rcov(:) = get_covalent_rad(mol%num)

call new_exp_ncoord(exp_ncoord, mol, cutoff=cutoff, rcov=rcov)
call test_cn_gen(error, mol, exp_ncoord, cutoff, ref)
! Test also the external interface
call new_ncoord(exp_ncoord, mol, "exp", cutoff=cutoff, rcov=rcov)
call exp_ncoord%get_cn(mol, cn)

if (any(abs(cn - ref) > thr)) then
call test_failed(error, "Coordination numbers do not match")
print'(3es21.14)', cn

Check warning on line 533 in test/test_ncoord.f90

View check run for this annotation

Codecov / codecov/patch

test/test_ncoord.f90#L533

Added line #L533 was not covered by tests
end if

end subroutine test_cn_mb01_exp


Expand Down Expand Up @@ -756,8 +770,9 @@ subroutine test_cn_mb01_erf(error)
type(error_type), allocatable, intent(out) :: error

type(structure_type) :: mol
type(erf_ncoord_type) :: erf_ncoord
class(ncoord_type), allocatable :: erf_ncoord
real(wp), allocatable :: rcov(:)
real(wp), allocatable :: cn(:)

real(wp), parameter :: cutoff = 30.0_wp
real(wp), parameter :: kcn = 2.60_wp
Expand All @@ -771,11 +786,17 @@ subroutine test_cn_mb01_erf(error)

call get_structure(mol, "mindless01")

allocate(rcov(mol%nid))
allocate(rcov(mol%nid), cn(mol%nat))
rcov(:) = get_covalent_rad(mol%num)

call new_erf_ncoord(erf_ncoord, mol, kcn=kcn, cutoff=cutoff, rcov=rcov)
call test_cn_gen(error, mol, erf_ncoord, cutoff, ref)
! Test also the external interface
call new_ncoord(erf_ncoord, mol, "erf", kcn=kcn, cutoff=cutoff, rcov=rcov)
call erf_ncoord%get_cn(mol, cn)

if (any(abs(cn - ref) > thr)) then
call test_failed(error, "Coordination numbers do not match")
print'(3es21.14)', cn

Check warning on line 798 in test/test_ncoord.f90

View check run for this annotation

Codecov / codecov/patch

test/test_ncoord.f90#L798

Added line #L798 was not covered by tests
end if

end subroutine test_cn_mb01_erf

Expand Down Expand Up @@ -1018,9 +1039,10 @@ subroutine test_cn_mb01_erf_en(error)
type(error_type), allocatable, intent(out) :: error

type(structure_type) :: mol
type(erf_en_ncoord_type) :: erf_en_ncoord
class(ncoord_type), allocatable :: erf_en_ncoord
real(wp), allocatable :: rcov(:)
real(wp), allocatable :: en(:)
real(wp), allocatable :: cn(:)

real(wp), parameter :: cutoff = 30.0_wp
real(wp), parameter :: kcn = 2.60_wp
Expand All @@ -1034,12 +1056,19 @@ subroutine test_cn_mb01_erf_en(error)

call get_structure(mol, "mindless01")

allocate(rcov(mol%nid), en(mol%nid))
allocate(rcov(mol%nid), en(mol%nid), cn(mol%nat))
rcov(:) = get_covalent_rad(mol%num)
en(:) = get_pauling_en(mol%num)

call new_erf_en_ncoord(erf_en_ncoord, mol, kcn=kcn, cutoff=cutoff, rcov=rcov, en=en)
call test_cn_gen(error, mol, erf_en_ncoord, cutoff, ref)
! Test also the external interface
call new_ncoord(erf_en_ncoord, mol, "erf_en", &
& kcn=kcn, cutoff=cutoff, rcov=rcov, en=en)
call erf_en_ncoord%get_cn(mol, cn)

if (any(abs(cn - ref) > thr)) then
call test_failed(error, "Coordination numbers do not match")
print'(3es21.14)', cn

Check warning on line 1070 in test/test_ncoord.f90

View check run for this annotation

Codecov / codecov/patch

test/test_ncoord.f90#L1070

Added line #L1070 was not covered by tests
end if

end subroutine test_cn_mb01_erf_en

Expand Down Expand Up @@ -1299,9 +1328,10 @@ subroutine test_cn_mb01_erf_dftd4(error)
type(error_type), allocatable, intent(out) :: error

type(structure_type) :: mol
type(erf_dftd4_ncoord_type) :: erf_dftd4_ncoord
class(ncoord_type), allocatable :: erf_dftd4_ncoord
real(wp), allocatable :: rcov(:)
real(wp), allocatable :: en(:)
real(wp), allocatable :: cn(:)

real(wp), parameter :: cutoff = 30.0_wp
real(wp), parameter :: ref(16) = [&
Expand All @@ -1314,12 +1344,19 @@ subroutine test_cn_mb01_erf_dftd4(error)

call get_structure(mol, "mindless01")

allocate(rcov(mol%nid), en(mol%nid))
allocate(rcov(mol%nid), en(mol%nid), cn(mol%nat))
rcov(:) = get_covalent_rad(mol%num)
en(:) = get_pauling_en(mol%num)

call new_erf_dftd4_ncoord(erf_dftd4_ncoord, mol, cutoff=cutoff, rcov=rcov, en=en)
call test_cn_gen(error, mol, erf_dftd4_ncoord, cutoff, ref)
! Test also the external interface
call new_ncoord(erf_dftd4_ncoord, mol, "dftd4", &
& cutoff=cutoff, rcov=rcov, en=en)
call erf_dftd4_ncoord%get_cn(mol, cn)

if (any(abs(cn - ref) > thr)) then
call test_failed(error, "Coordination numbers do not match")
print'(3es21.14)', cn

Check warning on line 1358 in test/test_ncoord.f90

View check run for this annotation

Codecov / codecov/patch

test/test_ncoord.f90#L1358

Added line #L1358 was not covered by tests
end if

end subroutine test_cn_mb01_erf_dftd4

Expand Down

0 comments on commit 1318341

Please sign in to comment.