iexciting-0.9.224
[exciting.git] / src / vnlrho.f90
blob0678f13f54f86f0eae525860f8e165498b28b34c
2 ! Copyright (C) 2002-2005 J. K. Dewhurst, S. Sharma and C. Ambrosch-Draxl.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
6 !BOP
7 ! !ROUTINE: vnlrho
8 ! !INTERFACE:
9 subroutine vnlrho(tsh,wfmt1,wfmt2,wfir1,wfir2,zrhomt,zrhoir)
10 ! !USES:
11 use modmain
12 ! !INPUT/OUTPUT PARAMETERS:
13 ! tsh : .true. if the muffin-tin density is to be in spherical harmonics
14 ! (in,logical)
15 ! wfmt1 : muffin-tin part of wavefunction 1 in spherical coordinates
16 ! (in,complex(lmmaxvr,nrcmtmax,natmtot,nspinor))
17 ! wfmt2 : muffin-tin part of wavefunction 2 in spherical coordinates
18 ! (in,complex(lmmaxvr,nrcmtmax,natmtot,nspinor))
19 ! wfir1 : interstitial wavefunction 1 (in,complex(ngrtot))
20 ! wfir2 : interstitial wavefunction 2 (in,complex(ngrtot))
21 ! zrhomt : muffin-tin charge density in spherical harmonics/coordinates
22 ! (out,complex(lmmaxvr,nrcmtmax,natmtot))
23 ! zrhoir : interstitial charge density (out,complex(ngrtot))
24 ! !DESCRIPTION:
25 ! Calculates the complex overlap charge density from two input wavefunctions:
26 ! $$ \rho({\bf r})\equiv\Psi_1^{\dag}({\bf r})\cdot\Psi_2({\bf r}). $$
27 ! Note that the muffin-tin wavefunctions are provided in spherical coordinates
28 ! and the returned density is either in terms of spherical harmonic
29 ! coefficients or spherical coordinates when {\tt tsh} is {\tt .true.} or
30 ! {\tt .false.}, respectively. See also the routine {\tt vnlrhomt}.
32 ! !REVISION HISTORY:
33 ! Created November 2004 (Sharma)
34 !EOP
35 !BOC
36 implicit none
37 ! arguments
38 logical, intent(in) :: tsh
39 complex(8), intent(in) :: wfmt1(lmmaxvr,nrcmtmax,natmtot,nspinor)
40 complex(8), intent(in) :: wfmt2(lmmaxvr,nrcmtmax,natmtot,nspinor)
41 complex(8), intent(in) :: wfir1(ngrtot,nspinor)
42 complex(8), intent(in) :: wfir2(ngrtot,nspinor)
43 complex(8), intent(out) :: zrhomt(lmmaxvr,nrcmtmax,natmtot)
44 complex(8), intent(out) :: zrhoir(ngrtot)
45 ! local variables
46 integer is,ia,ias,nrc,ir
47 ! allocatable arrays
48 complex(8), allocatable :: zfmt(:,:)
49 if (spinpol) allocate(zfmt(lmmaxvr,nrcmtmax))
50 ! muffin-tin part
51 do is=1,nspecies
52 nrc=nrcmt(is)
53 do ia=1,natoms(is)
54 ias=idxas(ia,is)
55 call vnlrhomt(tsh,is,wfmt1(:,:,ias,1),wfmt2(:,:,ias,1),zrhomt(:,:,ias))
56 if (spinpol) then
57 ! spin-polarised
58 call vnlrhomt(tsh,is,wfmt1(:,:,ias,2),wfmt2(:,:,ias,2),zfmt)
59 zrhomt(:,1:nrc,ias)=zrhomt(:,1:nrc,ias)+zfmt(:,1:nrc)
60 end if
61 end do
62 end do
63 ! interstitial part
64 if (spinpol) then
65 ! spin-polarised
66 do ir=1,ngrtot
67 zrhoir(ir)=conjg(wfir1(ir,1))*wfir2(ir,1)+conjg(wfir1(ir,2))*wfir2(ir,2)
68 end do
69 else
70 ! spin-unpolarised
71 do ir=1,ngrtot
72 zrhoir(ir)=conjg(wfir1(ir,1))*wfir2(ir,1)
73 end do
74 end if
75 if (spinpol) deallocate(zfmt)
76 return
77 end subroutine
78 !EOC