Skip to content

Commit

Permalink
Reduced number of operations in dyn_nonanalytic.
Browse files Browse the repository at this point in the history
  • Loading branch information
nakib committed Jun 19, 2023
1 parent 1df91d1 commit e38ec3b
Showing 1 changed file with 8 additions and 9 deletions.
17 changes: 8 additions & 9 deletions src/wannier.f90
Original file line number Diff line number Diff line change
Expand Up @@ -145,12 +145,10 @@ subroutine read_exciting_Wannier(self, num)
type(numerics), intent(in) :: num

!Local variables
integer(i64) :: iuc, iuc_el, iuc_ph, ib, jb, image
integer(i64) :: iuc, ib, image
integer(i64) :: ignore_i
real(r64) :: ignore_3r(3)
complex(r64), allocatable :: gwann_aux(:, :, :, :, :)
integer(i64), allocatable :: rcells_g_aux(:, :)
integer(i64), allocatable :: gwsdeg_aux(:)

! EXCITING File names:
character(len=*), parameter :: filename_gwann = "eph_grr.bin"
Expand Down Expand Up @@ -535,7 +533,7 @@ subroutine ph_wann(self, crys, nq, qvecs, energies, evecs, velocities)
complex(r64), intent(out), optional :: evecs(nq, self%numbranches, self%numbranches)

!Local variables
integer(i64) :: iuc, ipol, jpol, ib, jb, iq, na, nb, nwork, aux
integer(i64) :: iuc, ipol, ib, jb, iq, na, nb, nwork, aux
real(r64) :: rcart(3)
complex(r64) :: caux
real(r64), allocatable :: rwork(:)
Expand Down Expand Up @@ -695,9 +693,9 @@ subroutine dyn_nonanalytic(crys, q, num_cells, dyn_l, ddyn_l)
complex(r64), optional, intent(out) :: ddyn_l(:, :, :)

!Local variables
complex(r64) :: fnat(3), facqd, facq
complex(r64) :: fnat(3), facqd, facq, oneIrr(3)
real(r64) :: qeq, arg, zig(3), zjg(3), g(3), gmax, alph, &
tpiba, dgeg(3), rr(crys%numatoms,crys%numatoms,3), fac
tpiba, dgeg(3), rr(crys%numatoms,crys%numatoms,3), fac, dgeg_coeff
integer(i64) :: iat, jat, idim, jdim, ipol, jpol, &
m1, m2, m3, nq1, nq2, nq3

Expand Down Expand Up @@ -756,12 +754,14 @@ subroutine dyn_nonanalytic(crys, q, num_cells, dyn_l, ddyn_l)
if(qeq > 0.0_r64 .and. qeq/alph/4.0_r64 < gmax) then
facqd = exp(-qeq/alph/4.0_r64)/qeq
dgeg = matmul(crys%epsilon + transpose(crys%epsilon), g)
dgeg_coeff = 0.25_r64/alph + 1.0_r64/qeq

do iat = 1, crys%numatoms
zig(:) = matmul(g, crys%born(:, :, iat))

do jat = 1,crys%numatoms
rr(iat, jat,:) = (crys%basis_cart(:, iat) - crys%basis_cart(:, jat))/bohr2nm
rr(iat, jat, :) = (crys%basis_cart(:, iat) - crys%basis_cart(:, jat))/bohr2nm
oneIrr(:) = oneI*rr(iat, jat, :)
zjg(:) = matmul(g, crys%born(:, :, jat))
arg = dot_product(g, rr(iat, jat, :))
facq = facqd*expi(arg)
Expand All @@ -777,8 +777,7 @@ subroutine dyn_nonanalytic(crys, q, num_cells, dyn_l, ddyn_l)
ddyn_l(idim, jdim, :) = ddyn_l(idim, jdim, :) + &
facq*&
(zjg(jpol)*crys%born(:, ipol, iat) + zig(ipol)*crys%born(:, jpol, jat) + &
zig(ipol)*zjg(jpol)*(oneI*rr(iat, jat, :) - &
dgeg(:)*(0.25_r64/alph + 1.0_r64/qeq)))
zig(ipol)*zjg(jpol)*(oneIrr(:) - dgeg_coeff*dgeg(:)))
end if
end do
end do
Expand Down

0 comments on commit e38ec3b

Please sign in to comment.