Skip to content

Commit

Permalink
Merge remote-tracking branch 'bhourahine/redundantVariables'
Browse files Browse the repository at this point in the history
  • Loading branch information
aradi committed Feb 26, 2018
2 parents 7bd86db + fdfe5a0 commit 3d3d54f
Show file tree
Hide file tree
Showing 7 changed files with 329 additions and 545 deletions.
38 changes: 17 additions & 21 deletions lib/api.f90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module dftd3_api

!> C6 max flags (or unallocated if not needed)
logical, allocatable :: maxc6list(:)

!> Real space cutoff in atomic units.
real(wp) :: cutoff = sqrt(9000.0_wp)

Expand Down Expand Up @@ -101,19 +101,19 @@ subroutine dftd3_init(this, input)
maxc6list(:) = .false.
end if
maxc6 = any(maxc6list)

allocate(this%c6ab(max_elem, max_elem, maxc, maxc, 3))
allocate(this%mxc(max_elem))
call copyc6("", maxc, max_elem, this%c6ab, this%mxc, minc6, minc6list, &
call copyc6(maxc, max_elem, this%c6ab, this%mxc, minc6, minc6list, &
& maxc6, maxc6list)
this%rthr = input%cutoff**2
this%cn_thr = input%cutoff_cn**2
allocate(this%r0ab(max_elem, max_elem))
call setr0ab(max_elem, autoang, this%r0ab)

end subroutine dftd3_init


!> Sets the parameter for the dftd3 calculator by choosing a functional.
!!
!! \param func Name of the functional.
Expand All @@ -129,13 +129,13 @@ subroutine dftd3_set_functional(this, func, version, tz)
this%version = version
call setfuncpar(func, this%version, tz, this%s6, this%rs6, this%s18, &
& this%rs18, this%alp)

end subroutine dftd3_set_functional


!> Sets the parameter for the dftd3 calculator directly.
!!
!! \param pars Parameter to use. The 5 parameters must follow the same
!! \param pars Parameter to use. The 5 parameters must follow the same
!! order as when specified in the dftd3.local file for the dftd3 program.
!! (see the documentation of the dftd3 program for details)
!! \param version Version to use. Note, that depending on the version the
Expand All @@ -157,7 +157,7 @@ subroutine dftd3_set_params(this, pars, version)
this%rs18 = pars(4)
this%alp = pars(5)
this%version = version

end subroutine dftd3_set_params


Expand All @@ -178,20 +178,18 @@ subroutine dftd3_dispersion(this, coords, izp, disp, grads)

logical, allocatable :: fix(:)
integer :: natom
real(wp) :: s6, s18, rs6, rs8, rs10, alp6, alp8, alp10
real(wp) :: s6, s18, rs6, rs8, alp6, alp8
real(wp) :: e6, e8, e10, e12, e6abc, gdsp, gnorm

natom = size(coords, dim=2)
s6 = this%s6
s18 = this%s18
rs6 = this%rs6
rs8 = this%rs18
rs10 = this%rs18
alp6 = this%alp
alp8 = alp6 + 2.0_wp
alp10 = alp8 + 2.0_wp
call edisp(max_elem, maxc, natom, coords, izp, this%c6ab, this%mxc, &
& r2r4, this%r0ab, rcov, rs6, rs8, rs10, alp6, alp8, alp10, &
& r2r4, this%r0ab, rcov, rs6, rs8, alp6, alp8, &
& this%version, this%noabc, this%rthr, this%cn_thr, e6, e8, e10, e12, &
& e6abc)
disp = -e6 * this%s6 - e8 * this%s18 - e6abc
Expand All @@ -204,10 +202,10 @@ subroutine dftd3_dispersion(this, coords, izp, disp, grads)
fix(:) = .false.
grads(:,:) = 0.0_wp
call gdisp(max_elem, maxc, natom, coords, izp, this%c6ab, this%mxc, r2r4, &
& this%r0ab, rcov, s6, s18, rs6, rs8, rs10, alp6, alp8, alp10, &
& this%r0ab, rcov, s6, s18, rs6, rs8, alp6, alp8, &
& this%noabc, this%rthr, this%numgrad, this%version, .false., grads, &
& gdsp, gnorm, this%cn_thr, fix)

end subroutine dftd3_dispersion


Expand All @@ -231,7 +229,7 @@ subroutine dftd3_pbc_dispersion(this, coords, izp, latvecs, disp, grads, &
real(wp), optional, intent(out) :: grads(:,:), stress(:,:)

integer :: natom
real(wp) :: s6, s18, rs6, rs8, rs10, alp6, alp8, alp10
real(wp) :: s6, s18, rs6, rs8, alp6, alp8
real(wp) :: e6, e8, e10, e12, e6abc, gnorm, disp2
real(wp) :: rtmp3(3)
integer :: rep_cn(3), rep_vdw(3)
Expand All @@ -247,17 +245,15 @@ subroutine dftd3_pbc_dispersion(this, coords, izp, latvecs, disp, grads, &
s18 = this%s18
rs6 = this%rs6
rs8 = this%rs18
rs10 = this%rs18
alp6 = this%alp
alp8 = alp6 + 2.0_wp
alp10 = alp8 + 2.0_wp

call set_criteria(this%rthr, latvecs, rtmp3)
rep_vdw(:) = int(rtmp3) + 1
call set_criteria(this%cn_thr, latvecs, rtmp3)
rep_cn(:) = int(rtmp3) + 1
call pbcedisp(max_elem, maxc, natom, coords, izp, this%c6ab, this%mxc, &
& r2r4, this%r0ab, rcov, rs6, rs8, rs10, alp6, alp8, alp10, &
& r2r4, this%r0ab, rcov, rs6, rs8, alp6, alp8, &
& this%version, this%noabc, e6, e8, e10, e12, e6abc, latvecs, &
& this%rthr, rep_vdw, this%cn_thr, rep_cn)
disp = -e6 * this%s6 - e8 * this%s18 - e6abc
Expand All @@ -268,14 +264,14 @@ subroutine dftd3_pbc_dispersion(this, coords, izp, latvecs, disp, grads, &

grads(:,:) = 0.0_wp
call pbcgdisp(max_elem, maxc, natom, coords, izp, this%c6ab, this%mxc, &
& r2r4, this%r0ab, rcov, s6, s18, rs6, rs8, rs10, alp6, alp8, alp10, &
& r2r4, this%r0ab, rcov, s6, s18, rs6, rs8, alp6, alp8, &
& this%noabc, this%numgrad, this%version, grads, disp2, gnorm, &
& stress, latvecs, rep_vdw, rep_cn, this%rthr, .false., this%cn_thr)
! Note, the stress variable in pbcgdisp contains the *lattice derivatives*
! on return, so it needs to be converted to obtain the stress tensor.
stress(:,:) = -matmul(stress, transpose(latvecs))&
& / abs(determinant(latvecs))

end subroutine dftd3_pbc_dispersion


Expand All @@ -292,5 +288,5 @@ elemental function get_atomic_number(species) result(izp)

end function get_atomic_number


end module dftd3_api
18 changes: 9 additions & 9 deletions lib/common.f90
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ module dftd3_common
real(wp), parameter :: k3 = -4.


real(wp), parameter :: autoang =0.52917726d0
real(wp), parameter :: autoang = 0.52917726d0
real(wp), parameter :: autokcal = 627.509541d0
real(wp), parameter :: autoev = 27.21138505
! J/mol nm^6 - > au
Expand All @@ -58,23 +58,23 @@ module dftd3_common

contains

subroutine limit(iat,jat,iadr,jadr)
integer iat,jat,iadr,jadr,i
subroutine limit(iat,jat,iadr,jadr)
integer, intent(inout) :: iat,jat
integer, intent(out) :: iadr,jadr
integer :: i
iadr=1
jadr=1
i=100
10 if (iat.gt.100) then
do while (iat .gt. 100)
iat=iat-100
iadr=iadr+1
goto 10
end if
end do

i=100
20 if (jat.gt.100) then
do while (jat .gt.100)
jat=jat-100
jadr=jadr+1
goto 20
end if
end do

end subroutine limit

Expand Down
Loading

0 comments on commit 3d3d54f

Please sign in to comment.