The Elk Code
potefield.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2010 J. K. Dewhurst, S. Sharma and E. K. U. Gross.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
5 
6 subroutine potefield
7 use modmain
8 implicit none
9 ! local variables
10 integer is,ia,ias
11 integer nr,nri,ir
12 integer i,i1,i2,i3
13 real(8) ex,ey,ez,e,v0,r
14 real(8) f01,f11,f12,f13
15 real(8) v1(3),v2(3),t1,t2
16 ! external E-field in Cartesian coordinates
17 ex=efieldc(1); ey=efieldc(2); ez=efieldc(3)
18 e=sqrt(ex**2+ey**2+ez**2)
19 if (e > 1.d-8) then
20  ex=ex/e; ey=ey/e; ez=ez/e
21 else
22  return
23 end if
24 ! constant added to potential so that it is zero at the unit cell center
25 v1(:)=0.5d0*(avec(:,1)+avec(:,2)+avec(:,3))
26 v0=dot_product(efieldc(:),v1(:))
27 ! coefficients for real spherical harmonics R₁₋₁, R₁₀ and R₁₁
28 t1=e*sqrt(fourpi/3.d0)
29 f11=t1*ey
30 f12=-t1*ez
31 f13=t1*ex
32 ! muffin-tin potential
33 do ias=1,natmtot
34  is=idxis(ias)
35  ia=idxia(ias)
36  nr=nrmt(is)
37  nri=nrmti(is)
38 ! coefficient for R_00
39  f01=v0-dot_product(efieldc(:),atposc(:,ia,is))
40  f01=f01*y00i
41  i=1
42  do ir=1,nr
43  r=rlmt(ir,1,is)
44  vclmt(i,ias)=vclmt(i,ias)+f01
45  vclmt(i+1,ias)=vclmt(i+1,ias)+f11*r
46  vclmt(i+2,ias)=vclmt(i+2,ias)+f12*r
47  vclmt(i+3,ias)=vclmt(i+3,ias)+f13*r
48  if (ir <= nri) then
49  i=i+lmmaxi
50  else
51  i=i+lmmaxo
52  end if
53  end do
54 end do
55 ! interstitial potential
56 t2=0.5d0*vmaxefc
57 ir=0
58 do i3=0,ngridg(3)-1
59  v1(3)=dble(i3)/dble(ngridg(3))
60  do i2=0,ngridg(2)-1
61  v1(2)=dble(i2)/dble(ngridg(2))
62  do i1=0,ngridg(1)-1
63  v1(1)=dble(i1)/dble(ngridg(1))
64  ir=ir+1
65  call r3mv(avec,v1,v2)
66  t1=efieldc(1)*v2(1)+efieldc(2)*v2(2)+efieldc(3)*v2(3)
67  t1=v0-t1
68  if (abs(t1) < vmaxefc) then
69  vclir(ir)=vclir(ir)+t1
70  else
71  vclir(ir)=vclir(ir)+sign(t2,t1)
72  end if
73  end do
74  end do
75 end do
76 end subroutine
77 
integer, dimension(3) ngridg
Definition: modmain.f90:386
integer lmmaxo
Definition: modmain.f90:203
real(8), dimension(:,:,:), allocatable rlmt
Definition: modmain.f90:179
real(8), dimension(:,:), allocatable vclmt
Definition: modmain.f90:624
subroutine potefield
Definition: potefield.f90:7
real(8) vmaxefc
Definition: modmain.f90:320
real(8), dimension(3, 3) avec
Definition: modmain.f90:12
real(8), dimension(:), allocatable vclir
Definition: modmain.f90:624
integer, dimension(maxatoms *maxspecies) idxis
Definition: modmain.f90:44
integer lmmaxi
Definition: modmain.f90:207
real(8), parameter y00i
Definition: modmain.f90:1237
integer, dimension(maxatoms *maxspecies) idxia
Definition: modmain.f90:45
real(8), parameter fourpi
Definition: modmain.f90:1234
integer natmtot
Definition: modmain.f90:40
pure subroutine r3mv(a, x, y)
Definition: r3mv.f90:10
real(8), dimension(3, maxatoms, maxspecies) atposc
Definition: modmain.f90:54
integer, dimension(maxspecies) nrmti
Definition: modmain.f90:211
real(8), dimension(3) efieldc
Definition: modmain.f90:312
integer, dimension(maxspecies) nrmt
Definition: modmain.f90:150