Skip to content

Commit 7f1b63a

Browse files
committed
Minor changes in documentation and naming.
1 parent 6dbda9f commit 7f1b63a

File tree

2 files changed

+66
-15
lines changed

2 files changed

+66
-15
lines changed

lib/api.f90

+65-14
Original file line numberDiff line numberDiff line change
@@ -1,52 +1,66 @@
1+
!> This module contains the API to access DFT-D3 functionality.
2+
!!
13
module dftd3_api
24
use dftd3_sizes
35
use dftd3_common
46
use dftd3_core
57
implicit none
68
private
79

8-
public :: dftd3_input, dftd3_state
10+
public :: dftd3_input, dftd3_calc
911
public :: dftd3_init, dftd3_set_params, dftd3_set_functional
1012
public :: dftd3_dispersion, dftd3_pbc_dispersion
1113
public :: get_atomic_number
1214

1315

16+
!> Input for a dftd3 calculator.
17+
!!
1418
type :: dftd3_input
15-
! Whether three body term should be calculated
19+
!> Whether three body term should be calculated
1620
logical :: threebody = .false.
1721

18-
! Numerical gradients instead of analytical ones
22+
!> Whether numerical gradients instead of analytical ones
1923
logical :: numgrad = .false.
2024

21-
! C6 min flags (or unallocated if not needed)
25+
!> C6 min flags (or unallocated if not needed)
2226
logical, allocatable :: minc6list(:)
2327

24-
! C6 max flags (or unallocated if not needed)
28+
!> C6 max flags (or unallocated if not needed)
2529
logical, allocatable :: maxc6list(:)
2630

27-
! Real space cutoff
31+
!> Real space cutoff in atomic units.
2832
real(wp) :: cutoff = sqrt(9000.0_wp)
2933

30-
! Real space cutoff for coordination numbers
34+
!> Real space cutoff for coordination numbers in atomic units
3135
real(wp) :: cutoff_cn = sqrt(1600.0_wp)
3236
end type dftd3_input
3337

3438

35-
type :: dftd3_state
39+
!> State of a dftd3 calculator.
40+
!!
41+
type :: dftd3_calc
42+
private
3643
logical :: noabc, numgrad
3744
integer :: version
3845
real(wp) :: s6, rs6, s18, rs18, alp
3946
real(wp) :: rthr, cn_thr
4047
integer :: rep_vdw(3), rep_cn(3)
4148
real(wp), allocatable :: r0ab(:,:), c6ab(:,:,:,:,:)
4249
integer, allocatable :: mxc(:)
43-
end type dftd3_state
50+
end type dftd3_calc
4451

4552

4653
contains
4754

55+
!> Initializes a dftd3 calculator.
56+
!!
57+
!! \note You also need to call dftd3_set_functional() or dftd3_set_params()
58+
!! before you can make an actual calculation.
59+
!!
60+
!! \param input Input parameters for the calculator.
61+
!!
4862
subroutine dftd3_init(this, input)
49-
type(dftd3_state), intent(out) :: this
63+
type(dftd3_calc), intent(out) :: this
5064
type(dftd3_input), intent(in) :: input
5165

5266
logical, allocatable :: minc6list(:), maxc6list(:)
@@ -83,8 +97,14 @@ subroutine dftd3_init(this, input)
8397
end subroutine dftd3_init
8498

8599

100+
!> Sets the parameter for the dftd3 calculator by choosing a functional.
101+
!!
102+
!! \param func Name of the functional.
103+
!! \param version Version to use.
104+
!! \param tz Whether special TZ-parameters should be used.
105+
!!
86106
subroutine dftd3_set_functional(this, func, version, tz)
87-
type(dftd3_state), intent(inout) :: this
107+
type(dftd3_calc), intent(inout) :: this
88108
character(*), intent(in) :: func
89109
integer, intent(in) :: version
90110
logical, intent(in) :: tz
@@ -96,8 +116,16 @@ subroutine dftd3_set_functional(this, func, version, tz)
96116
end subroutine dftd3_set_functional
97117

98118

119+
!> Sets the parameter for the dftd3 calculator directly.
120+
!!
121+
!! \param pars Parameter to use. The 5 parameters must follow the same
122+
!! order as when specified in the dftd3.local file for the dftd3 program.
123+
!! (see the documentation of the dftd3 program for details)
124+
!! \param version Version to use. Note, that depending on the version the
125+
!! five parameters may have different (or no) meaning.
126+
!!
99127
subroutine dftd3_set_params(this, pars, version)
100-
type(dftd3_state), intent(inout) :: this
128+
type(dftd3_calc), intent(inout) :: this
101129
real(wp), intent(in) :: pars(:)
102130
integer, intent(in) :: version
103131

@@ -116,8 +144,16 @@ subroutine dftd3_set_params(this, pars, version)
116144
end subroutine dftd3_set_params
117145

118146

147+
!> Calculates the dispersion for a given non-periodic configuration.
148+
!!
149+
!! \param coords Coordinates of the atoms in atomic units. Shape: [3, nAtom].
150+
!! \param izp Atomic number of each atom. Shape: [nAtom]. You can determine
151+
!! the atomic number using the get_atomic_number() function.
152+
!! \param disp Calculated dispersion energy in atomic units.
153+
!! \param grads Calculated gradients in atomic units, if present.
154+
!!
119155
subroutine dftd3_dispersion(this, coords, izp, disp, grads)
120-
type(dftd3_state), intent(in) :: this
156+
type(dftd3_calc), intent(in) :: this
121157
real(wp), intent(in) :: coords(:,:)
122158
integer, intent(in) :: izp(:)
123159
real(wp), intent(out) :: disp
@@ -158,9 +194,19 @@ subroutine dftd3_dispersion(this, coords, izp, disp, grads)
158194
end subroutine dftd3_dispersion
159195

160196

197+
!> Calculates the dispersion for a given periodic configuration.
198+
!!
199+
!! \param coords Coordinates of the atoms in atomic units. Shape: [3, nAtom].
200+
!! \param izp Atomic number of each atom. Shape: [nAtom]. You can determine
201+
!! the atomic number using the get_atomic_number() function.
202+
!! \param latvecs Lattice vectors in atomic units. Shape: [3, 3].
203+
!! \param disp Calculated dispersion energy in atomic units.
204+
!! \param grads Calculated gradiens in atomic units, if present.
205+
!! \param stress Calculated stress tensor in atomic units, if present.
206+
!!
161207
subroutine dftd3_pbc_dispersion(this, coords, izp, latvecs, disp, grads, &
162208
& stress)
163-
type(dftd3_state), intent(in) :: this
209+
type(dftd3_calc), intent(in) :: this
164210
real(wp), intent(in) :: coords(:,:)
165211
integer, intent(in) :: izp(:)
166212
real(wp), intent(in) :: latvecs(:,:)
@@ -212,6 +258,11 @@ subroutine dftd3_pbc_dispersion(this, coords, izp, latvecs, disp, grads, &
212258
end subroutine dftd3_pbc_dispersion
213259

214260

261+
!> Returns the atomic number for a given species.
262+
!!
263+
!! \param species Chemical symbol of the species.
264+
!! \return Atomic number.
265+
!!
215266
elemental function get_atomic_number(species) result(izp)
216267
character(*), intent(in) :: species
217268
integer :: izp

test/testapi.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ program testapi
9494

9595

9696
type(dftd3_input) :: input
97-
type(dftd3_state) :: dftd3
97+
type(dftd3_calc) :: dftd3
9898
integer :: atnum(nAtoms)
9999
real(wp) :: edisp
100100
real(wp) :: grads(3, nAtoms), stress(3, 3)

0 commit comments

Comments
 (0)